
Zubin pushed to branch wip/9.12.3-backports at Glasgow Haskell Compiler / GHC Commits: 266d0649 by Ryan Hendrickson at 2025-09-16T14:41:06+05:30 haddock: Preserve indentation in multiline examples Intended for use with :{ :}, but doesn't look for those characters. Any consecutive lines with birdtracks will only have initial whitespace stripped up to the column of the first line. (cherry picked from commit 75cadf816544408f65d3baeec8092a7356d4b720) - - - - - d52b0a9c by Ryan Hendrickson at 2025-09-16T14:41:06+05:30 haddock: Fix links to type operators (cherry picked from commit a0adc30d892f14f543f39d5c45faccacbc28afb4) - - - - - 606822f0 by Ryan Hendrickson at 2025-09-16T14:41:06+05:30 haddock: Parse math even after ordinary characters Fixes a bug where math sections were not recognized if preceded by a character that isn't special (like space or a markup character). (cherry picked from commit 6558467c0e3a9b97141ec9f0cdbadf3550c5cd3c) - - - - - b072547d by Ryan Hendrickson at 2025-09-16T14:41:06+05:30 haddock: Document instances from other packages When attaching instances to `Interface`s, it isn't enough just to look for instances in the list of `Interface`s being processed. We also need to look in the modules on which they depend, including those outside of this package. Fixes #25147. Fixes #26079. (cherry picked from commit a26243fde4680271712a3d774e17f6cd6da4a652) - - - - - b8a0bddc by Zubin Duggal at 2025-09-16T14:41:06+05:30 haddock: Don't warn about missing link destinations for derived names. Fixes #26114 (cherry picked from commit 5dabc718a04bfc4d277c5ff7f815ee3d6b9670cb) - - - - - 0337f4ec by Zubin Duggal at 2025-09-16T14:41:06+05:30 Prepare 9.12.3 - - - - - 21 changed files: - configure.ac - docs/users_guide/9.12.3-notes.rst - testsuite/driver/testlib.py - testsuite/tests/haddock/haddock_testsuite/Makefile - + testsuite/tests/haddock/haddock_testsuite/T26114.hs - + testsuite/tests/haddock/haddock_testsuite/T26114.stdout - testsuite/tests/haddock/haddock_testsuite/all.T - testsuite/tests/polykinds/T14172.stderr - utils/haddock/CHANGES.md - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/LexParseRn.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs - utils/haddock/haddock-library/test/Documentation/Haddock/ParserSpec.hs - utils/haddock/haddock-test/src/Test/Haddock/Config.hs - utils/haddock/html-test/ref/Bug1004.html - utils/haddock/html-test/ref/PatternSyns.html - utils/haddock/html-test/ref/TypeOperators.html - utils/haddock/html-test/src/TypeOperators.hs Changes: ===================================== configure.ac ===================================== @@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.12.2], [glasgow-ha AC_CONFIG_MACRO_DIRS([m4]) # Set this to YES for a released version, otherwise NO -: ${RELEASE=YES} +: ${RELEASE=NO} # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line # above. If this is not a released version, then we will append the ===================================== docs/users_guide/9.12.3-notes.rst ===================================== @@ -13,6 +13,83 @@ Compiler - Fixed re-exports of ``MkSolo`` and ``MkSolo#`` (:ghc-ticket:`25182`) - Fixed the behavior of ``Language.Haskell.TH.mkName "FUN"`` (:ghc-ticket:`25174`) +- Fixed miscompilation involving ``zonkEqTypes`` on ``AppTy/AppTy`` (:ghc-ticket:`26256`) +- Fixed CprAnal to detect recursive newtypes (:ghc-ticket:`25944`) +- Fixed specialisation of incoherent instances (:ghc-ticket:`25883`) +- Fixed bytecode generation for ``tagToEnum# <LITERAL>`` (:ghc-ticket:`25975`) +- Fixed panic with EmptyCase and RequiredTypeArguments (:ghc-ticket:`25004`) +- Fixed ``tyConStupidTheta`` to handle ``PromotedDataCon`` (:ghc-ticket:`25739`) +- Fixed unused import warnings for duplicate record fields (:ghc-ticket:`24035`) +- Fixed lexing of ``"\^\"`` (:ghc-ticket:`25937`) +- Fixed string gap collapsing (:ghc-ticket:`25784`) +- Fixed lexing of comments in multiline strings (:ghc-ticket:`25609`) +- Made unexpected LLVM versions a warning rather than an error (:ghc-ticket:`25915`) +- Disabled ``-fprof-late-overloaded-calls`` for join points to avoid invalid transformations +- Fixed bugs in ``integerRecipMod`` and ``integerPowMod`` (:ghc-ticket:`26017`) +- Fixed ``naturalAndNot`` for NB/NS case (:ghc-ticket:`26230`) +- Fixed ``ds_ev_typeable`` to use ``mkTrAppChecked`` (:ghc-ticket:`25998`) +- Fixed GHC settings to always unescape escaped spaces (:ghc-ticket:`25204`) +- Fixed issue with HasCallStack constraint caching (:ghc-ticket:`25529`) +- Fixed archive member size writing logic in ``GHC.SysTools.Ar`` (:ghc-ticket:`26120`, :ghc-ticket:`22586`) + +Runtime System +~~~~~~~~~~~~~~ + +- Fixed ``MessageBlackHole.link`` to always be a valid closure +- Fixed handling of WHITEHOLE in ``messageBlackHole`` (:ghc-ticket:`26205`) +- Fixed ``rts_clearMemory`` logic when sanity checks are enabled (:ghc-ticket:`26011`) +- Fixed underflow frame lookups in the bytecode interpreter (:ghc-ticket:`25750`) +- Fixed overflows and reentrancy in interpreter statistics calculation (:ghc-ticket:`25756`) +- Fixed INTERP_STATS profiling code (:ghc-ticket:`25695`) +- Removed problematic ``n_free`` variable from nonmovingGC (:ghc-ticket:`26186`) +- Fixed incorrect format specifiers in era profiling +- Improved documentation of SLIDE and PACK bytecode instructions +- Eliminated redundant ``SLIDE x 0`` bytecode instructions +- Fixed compile issues on powerpc64 ELF v1 + +Code Generation +~~~~~~~~~~~~~~~ + +- Fixed LLVM built-in variable predicate (was checking ``$llvm`` instead of ``@llvm``) +- Fixed linkage of built-in arrays for LLVM (:ghc-ticket:`25769`) +- Fixed code generation for SSE vector operations (:ghc-ticket:`25859`) +- Fixed ``bswap64`` code generation on i386 (:ghc-ticket:`25601`) +- Fixed sub-word arithmetic right shift on AArch64 (:ghc-ticket:`26061`) +- Fixed LLVM vector literal emission to include type information +- Fixed LLVM version detection +- Fixed typo in ``padLiveArgs`` that caused segfaults (:ghc-ticket:`25770`, :ghc-ticket:`25773`) +- Fixed constant-folding for Word->Float bitcasts +- Added surface syntax for Word/Float bitcast operations +- Fixed ``MOVD`` format in x86 NCG for ``unpackInt64X2#`` +- Added ``-finter-module-far-jumps`` flag for AArch64 +- Fixed RV64 J instruction handling for non-local jumps (:ghc-ticket:`25738`) +- Reapplied division by constants optimization +- Fixed TNTC to set CmmProc entry_label properly (:ghc-ticket:`25565`) + +Linker +~~~~~~ + +- Improved efficiency of proddable blocks structure (:ghc-ticket:`26009`) +- Fixed Windows DLL loading to avoid redundant ``LoadLibraryEx`` calls (:ghc-ticket:`26009`) +- Fixed incorrect use of ``break`` in nested for loop (:ghc-ticket:`26052`) +- Fixed linker to not fail due to ``RTLD_NOW`` (:ghc-ticket:`25943`) +- Dropped obsolete Windows XP compatibility checks + +GHCi +~~~~ + +- Fixed ``mkTopLevEnv`` to use ``loadInterfaceForModule`` instead of ``loadSrcInterface`` (:ghc-ticket:`25951`) + +Template Haskell +~~~~~~~~~~~~~~~~ + +- Added explicit export lists to all remaining template-haskell modules + +Build system +~~~~~~~~~~~~~~~~ + +- Exposed all of Backtraces' internals for ghc-internal (:ghc-ticket:`26049`) +- Fixed cross-compilation configuration override (:ghc-ticket:`26236`) Included libraries ~~~~~~~~~~~~~~~~~~ ===================================== testsuite/driver/testlib.py ===================================== @@ -1725,7 +1725,7 @@ async def do_test(name: TestName, dst_makefile = in_testdir('Makefile') if src_makefile.exists(): makefile = src_makefile.read_text(encoding='UTF-8') - makefile = re.sub('TOP=.*', 'TOP=%s' % config.top, makefile, 1) + makefile = re.sub('TOP=.*', 'TOP=%s' % config.top, makefile, count=1) dst_makefile.write_text(makefile, encoding='UTF-8') if opts.pre_cmd: ===================================== testsuite/tests/haddock/haddock_testsuite/Makefile ===================================== @@ -76,3 +76,7 @@ hypsrcTest: .PHONY: haddockForeignTest haddockForeignTest: '$(HADDOCK)' A.hs B.hs F.hs arith.c + +.PHONY: T26114 +T26114: + '$(HADDOCK)' T26114.hs ===================================== testsuite/tests/haddock/haddock_testsuite/T26114.hs ===================================== @@ -0,0 +1,23 @@ +{-# LANGUAGE TypeFamilies #-} + +-- | Module +module T26114 where + +-- | C1 +class C1 t where + type C2 t + +-- | A +data A = A + +instance C1 A where + type C2 A = B + +-- | B +data B = B + +instance C1 B where + type C2 B = C + +-- | C +data C = C ===================================== testsuite/tests/haddock/haddock_testsuite/T26114.stdout ===================================== @@ -0,0 +1,3 @@ +[1 of 1] Compiling T26114 ( T26114.hs, nothing ) +Haddock coverage: + 100% ( 5 / 5) in 'T26114' ===================================== testsuite/tests/haddock/haddock_testsuite/all.T ===================================== @@ -24,3 +24,8 @@ test('haddockForeignTest', [ignore_stdout, ignore_stderr, req_haddock, extra_files(['./haddock-th-foreign-repro/A.hs', './haddock-th-foreign-repro/B.hs', './haddock-th-foreign-repro/F.hs', './haddock-th-foreign-repro/arith.c'])], makefile_test, ['haddockForeignTest']) + +test('T26114', + [ignore_stderr, req_haddock, extra_files(['T26114.hs'])], + makefile_test, + ['T26114']) ===================================== testsuite/tests/polykinds/T14172.stderr ===================================== @@ -1,6 +1,6 @@ T14172.hs:7:46: error: [GHC-88464] - • Found type wildcard ‘_’ standing for ‘a'1 :: k0’ - Where: ‘k0’ is an ambiguous type variable + • Found type wildcard ‘_’ standing for ‘a'1 :: k30’ + Where: ‘k30’ is an ambiguous type variable ‘a'1’ is an ambiguous type variable To use the inferred type, enable PartialTypeSignatures • In the first argument of ‘h’, namely ‘_’ ===================================== utils/haddock/CHANGES.md ===================================== @@ -1,6 +1,8 @@ ## Changes in 2.32.0 * Add highlighting for inline-code-blocks (sections enclosed in @'s) + * Fix missing documentation for orphan instances from other packages. + * Add incremental mode to support rendering documentation one module at a time. * The flag `--no-compilation` has been added. This flag causes Haddock to avoid ===================================== utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs ===================================== @@ -93,7 +93,10 @@ attachInstances expInfo ifaces instIfaceMap isOneShot = do , fromOrig == Just True || not (null reExp) ] mods_to_load = moduleSetElts mods - mods_visible = mkModuleSet $ map ifaceMod ifaces + -- We need to ensure orphans in modules outside of this package are included. + -- See https://gitlab.haskell.org/ghc/ghc/-/issues/25147 + -- and https://gitlab.haskell.org/ghc/ghc/-/issues/26079 + mods_visible = mkModuleSet $ concatMap (liftA2 (:) ifaceMod ifaceOrphanDeps) ifaces (_msgs, mb_index) <- do hsc_env <- getSession ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -59,6 +59,7 @@ import GHC.Types.Name.Set import GHC.Types.SafeHaskell import qualified GHC.Types.SrcLoc as SrcLoc import qualified GHC.Types.Unique.Map as UniqMap +import GHC.Unit.Module.Deps (dep_orphs) import GHC.Unit.Module.ModIface import GHC.Unit.State (PackageName (..), UnitState) import GHC.Utils.Outputable (SDocContext) @@ -270,6 +271,7 @@ createInterface1' flags unit_state dflags hie_file mod_iface ifaces inst_ifaces , ifaceVisibleExports = visible_names , ifaceFixMap = fixities , ifaceInstances = instances + , ifaceOrphanDeps = dep_orphs $ mi_deps mod_iface , ifaceOrphanInstances = [] -- Filled in attachInstances , ifaceRnOrphanInstances = [] -- Filled in renameInterfaceRn , ifaceHaddockCoverage = coverage ===================================== utils/haddock/haddock-api/src/Haddock/Interface/LexParseRn.hs ===================================== @@ -155,6 +155,7 @@ rename sDocContext renamer = rn | otherwise = isTermVarOrFieldNameSpace typeNsChoices | isDataOcc occ = isTcClsNameSpace + | isSymOcc occ = isTcClsNameSpace | otherwise = isTvNameSpace -- Generate the choices for the possible kind of thing this -- is. We narrow down the possibilities with the namespace (if ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs ===================================== @@ -104,6 +104,7 @@ renameInterface dflags ignoreSet renamingEnv warnings hoogle iface = do && isExternalName name && not (isBuiltInSyntax name) && not (isTyVarName name) + && not (isDerivedOccName $ nameOccName name) && Exact name /= eqTyCon_RDR -- Must not be in the set of ignored symbols for the module or the -- unqualified ignored symbols ===================================== utils/haddock/haddock-api/src/Haddock/Types.hs ===================================== @@ -131,6 +131,9 @@ data Interface = Interface -- Names from modules that are entirely re-exported don't count as visible. , ifaceInstances :: [ClsInst] -- ^ Instances exported by the module. + , ifaceOrphanDeps :: [Module] + -- ^ The list of modules to check for orphan instances if this module is + -- imported. , ifaceOrphanInstances :: [DocInstance GhcRn] -- ^ Orphan instances , ifaceRnOrphanInstances :: [DocInstance DocNameI] ===================================== utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ViewPatterns #-} @@ -28,6 +29,7 @@ import Control.Applicative import Control.Arrow (first) import Control.Monad import Data.Char (chr, isAlpha, isSpace, isUpper) +import Data.Functor (($>)) import Data.List (elemIndex, intercalate, intersperse, unfoldr) import Data.Maybe (fromMaybe, mapMaybe) import Data.Monoid @@ -186,11 +188,29 @@ specialChar = "_/<@\"&'`#[ " -- to ensure that we have already given a chance to more meaningful parsers -- before capturing their characters. string' :: Parser (DocH mod a) -string' = DocString . unescape . T.unpack <$> takeWhile1_ (`notElem` specialChar) +string' = + DocString + <$> ((:) <$> rawOrEscChar "" <*> many (rawOrEscChar "([")) + -- After the first character, stop for @\(@ or @\[@ math starters. (The + -- first character won't start a valid math string because this parser + -- should follow math parsers. But this parser is expected to accept at + -- least one character from all inputs that don't start with special + -- characters, so the first character parser can't have the @"(["@ + -- restriction.) where - unescape "" = "" - unescape ('\\' : x : xs) = x : unescape xs - unescape (x : xs) = x : unescape xs + -- | Parse a single logical character, either raw or escaped. Don't accept + -- escaped characters from the argument string. + rawOrEscChar :: [Char] -> Parser Char + rawOrEscChar restrictedEscapes = try $ Parsec.noneOf specialChar >>= \case + -- Handle backslashes: + -- - Fail on forbidden escape characters. + -- - Non-forbidden characters: simply unescape, e.g. parse "\b" as 'b', + -- - Trailing backslash: treat it as a raw backslash, not an escape + -- sequence. (This is the logic that this parser followed when this + -- comment was written; it is not necessarily intentional but now I + -- don't want to break anything relying on it.) + '\\' -> Parsec.noneOf restrictedEscapes <|> Parsec.eof $> '\\' + c -> pure c -- | Skips a single special character and treats it as a plain string. -- This is done to skip over any special characters belonging to other @@ -795,31 +815,33 @@ stripSpace = fromMaybe <*> mapM strip' -- | Parses examples. Examples are a paragraph level entity (separated by an empty line). -- Consecutive examples are accepted. examples :: Parser (DocH mod a) -examples = DocExamples <$> (many (try (skipHorizontalSpace *> "\n")) *> go) +examples = DocExamples <$> (many (try (skipHorizontalSpace *> "\n")) *> go Nothing) where - go :: Parser [Example] - go = do + go :: Maybe Text -> Parser [Example] + go mbInitialIndent = do prefix <- takeHorizontalSpace <* ">>>" + initialIndent <- maybe takeHorizontalSpace pure mbInitialIndent expr <- takeLine - (rs, es) <- resultAndMoreExamples - return (makeExample prefix expr rs : es) + (rs, es) <- resultAndMoreExamples (Just initialIndent) + return (makeExample prefix initialIndent expr rs : es) + + resultAndMoreExamples :: Maybe Text -> Parser ([Text], [Example]) + resultAndMoreExamples mbInitialIndent = choice' [moreExamples, result, pure ([], [])] where - resultAndMoreExamples :: Parser ([Text], [Example]) - resultAndMoreExamples = choice' [moreExamples, result, pure ([], [])] - where - moreExamples :: Parser ([Text], [Example]) - moreExamples = (,) [] <$> go + moreExamples :: Parser ([Text], [Example]) + moreExamples = (,) [] <$> go mbInitialIndent - result :: Parser ([Text], [Example]) - result = first . (:) <$> nonEmptyLine <*> resultAndMoreExamples + result :: Parser ([Text], [Example]) + result = first . (:) <$> nonEmptyLine <*> resultAndMoreExamples Nothing - makeExample :: Text -> Text -> [Text] -> Example - makeExample prefix expression res = - Example (T.unpack (T.strip expression)) result + makeExample :: Text -> Text -> Text -> [Text] -> Example + makeExample prefix indent expression res = + Example (T.unpack (tryStripIndent (T.stripEnd expression))) result where result = map (T.unpack . substituteBlankLine . tryStripPrefix) res tryStripPrefix xs = fromMaybe xs (T.stripPrefix prefix xs) + tryStripIndent = liftA2 fromMaybe T.stripStart (T.stripPrefix indent) substituteBlankLine "<BLANKLINE>" = "" substituteBlankLine xs = xs ===================================== utils/haddock/haddock-library/test/Documentation/Haddock/ParserSpec.hs ===================================== @@ -284,6 +284,13 @@ spec = do it "supports title for deprecated picture syntax" $ do "<<b a z>>" `shouldParseTo` image "b" "a z" + context "when parsing inline math" $ do + it "accepts inline math immediately after punctuation" $ do + "(\\(1 + 2 = 3\\) is an example of addition)" + `shouldParseTo` "(" + <> DocMathInline "1 + 2 = 3" + <> " is an example of addition)" + context "when parsing display math" $ do it "accepts markdown syntax for display math containing newlines" $ do "\\[\\pi\n\\pi\\]" `shouldParseTo` DocMathDisplay "\\pi\n\\pi" @@ -864,6 +871,29 @@ spec = do it "accepts unicode in examples" $ do ">>> 灼眼\nシャナ" `shouldParseTo` DocExamples [Example "灼眼" ["シャナ"]] + it "preserves indentation in consecutive example lines" $ do + unlines + [ ">>> line 1" + , ">>> line 2" + , ">>> line 3" + ] + `shouldParseTo` DocExamples + [ Example "line 1" [] + , Example " line 2" [] + , Example "line 3" [] + ] + + it "resets indentation after results" $ do + unlines + [ ">>> line 1" + , "result" + , ">>> line 2" + ] + `shouldParseTo` DocExamples + [ Example "line 1" ["result"] + , Example "line 2" [] + ] + context "when prompt is prefixed by whitespace" $ do it "strips the exact same amount of whitespace from result lines" $ do unlines ===================================== utils/haddock/haddock-test/src/Test/Haddock/Config.hs ===================================== @@ -262,6 +262,7 @@ baseDependencies ghcPath = do pkgs = [ "array" , "base" + , "deepseq" , "ghc-prim" , "process" , "template-haskell" ===================================== utils/haddock/html-test/ref/Bug1004.html ===================================== @@ -797,7 +797,61 @@ ><tr ><td class="src clearfix" > (NFData1 f, NFData1 g) => NFData1 (Product f g) #
Since: deepseq-1.4.3.0
Defined in Control.DeepSeq
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Applicative:10" ></span > (<a href="#" title="Control.Applicative" >Applicative</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Functor:11" ></span > (<a href="#" title="Control.Monad" >Functor</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Monad:12" ></span > (<a href="#" title="Control.Monad" >Monad</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadPlus:13" ></span > (<a href="#" title="Control.Monad" >MonadPlus</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadFix:14" ></span > (<a href="#" title="Control.Monad.Fix" >MonadFix</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadZip:15" ></span > (<a href="#" title="Control.Monad.Zip" >MonadZip</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Foldable:16" ></span > (<a href="#" title="Data.Foldable" >Foldable</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Traversable:17" ></span > (<a href="#" title="Data.Traversable" >Traversable</tr ><tr >
Note: in deepseq-1.5.0.0
this instance's superclasses were changed.
Since: deepseq-1.4.3.0
Defined in Control.DeepSeq
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Semigroup:20" ></span > (<a href="#" title="Prelude" >Semigroup</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Eq:21" > (Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => (Eq (f a), Eq (g a)) => Eq (Product f g a) #
Since: base-4.18.0.0
Since: base-4.18.0.0
Defined in Data.Functor.Product
Methods
compare :: Product f g a -> Product f g a -> Ordering #
(<) :: Product f g a -> Product f g a -> Bool #
(<=) :: Product f g a -> Product f g a -> Bool #
(>) :: Product f g a -> Product f g a -> Bool #
(>=) :: Product f g a -> Product f g a -> Bool #
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Generic:24" ></span > <a href="#" title="GHC.Generics" >Generic</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Read:25" ></span > (<a href="#" title="Prelude" >Read</tr ><tr >
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Show:26" ></span > (<a href="#" title="Prelude" >Show</tr ><tr >
Since: base-4.18.0.0
Since: base-4.18.0.0
Defined in Data.Functor.Product
Methods
compare :: Product f g a -> Product f g a -> Ordering #
(<) :: Product f g a -> Product f g a -> Bool #
(<=) :: Product f g a -> Product f g a -> Bool #
(>) :: Product f g a -> Product f g a -> Bool #
(>=) :: Product f g a -> Product f g a -> Bool #
<tr ><td class="src clearfix" ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep:28" ></span > <span class="keyword" >type</tr ><tr >
</p ><div class="doc" >
Doc for ( Description
><
Doc for (><</code
>)</p
></div
>
participants (1)