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
-
d52b0a9c
by Ryan Hendrickson at 2025-09-16T14:41:06+05:30
-
606822f0
by Ryan Hendrickson at 2025-09-16T14:41:06+05:30
-
b072547d
by Ryan Hendrickson at 2025-09-16T14:41:06+05:30
-
b8a0bddc
by Zubin Duggal at 2025-09-16T14:41:06+05:30
-
0337f4ec
by Zubin Duggal at 2025-09-16T14:41:06+05:30
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:
| ... | ... | @@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.12.2], [glasgow-ha |
| 22 | 22 | AC_CONFIG_MACRO_DIRS([m4])
|
| 23 | 23 | |
| 24 | 24 | # Set this to YES for a released version, otherwise NO
|
| 25 | -: ${RELEASE=YES}
|
|
| 25 | +: ${RELEASE=NO}
|
|
| 26 | 26 | |
| 27 | 27 | # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
|
| 28 | 28 | # above. If this is not a released version, then we will append the
|
| ... | ... | @@ -13,6 +13,83 @@ Compiler |
| 13 | 13 | |
| 14 | 14 | - Fixed re-exports of ``MkSolo`` and ``MkSolo#`` (:ghc-ticket:`25182`)
|
| 15 | 15 | - Fixed the behavior of ``Language.Haskell.TH.mkName "FUN"`` (:ghc-ticket:`25174`)
|
| 16 | +- Fixed miscompilation involving ``zonkEqTypes`` on ``AppTy/AppTy`` (:ghc-ticket:`26256`)
|
|
| 17 | +- Fixed CprAnal to detect recursive newtypes (:ghc-ticket:`25944`)
|
|
| 18 | +- Fixed specialisation of incoherent instances (:ghc-ticket:`25883`)
|
|
| 19 | +- Fixed bytecode generation for ``tagToEnum# <LITERAL>`` (:ghc-ticket:`25975`)
|
|
| 20 | +- Fixed panic with EmptyCase and RequiredTypeArguments (:ghc-ticket:`25004`)
|
|
| 21 | +- Fixed ``tyConStupidTheta`` to handle ``PromotedDataCon`` (:ghc-ticket:`25739`)
|
|
| 22 | +- Fixed unused import warnings for duplicate record fields (:ghc-ticket:`24035`)
|
|
| 23 | +- Fixed lexing of ``"\^\"`` (:ghc-ticket:`25937`)
|
|
| 24 | +- Fixed string gap collapsing (:ghc-ticket:`25784`)
|
|
| 25 | +- Fixed lexing of comments in multiline strings (:ghc-ticket:`25609`)
|
|
| 26 | +- Made unexpected LLVM versions a warning rather than an error (:ghc-ticket:`25915`)
|
|
| 27 | +- Disabled ``-fprof-late-overloaded-calls`` for join points to avoid invalid transformations
|
|
| 28 | +- Fixed bugs in ``integerRecipMod`` and ``integerPowMod`` (:ghc-ticket:`26017`)
|
|
| 29 | +- Fixed ``naturalAndNot`` for NB/NS case (:ghc-ticket:`26230`)
|
|
| 30 | +- Fixed ``ds_ev_typeable`` to use ``mkTrAppChecked`` (:ghc-ticket:`25998`)
|
|
| 31 | +- Fixed GHC settings to always unescape escaped spaces (:ghc-ticket:`25204`)
|
|
| 32 | +- Fixed issue with HasCallStack constraint caching (:ghc-ticket:`25529`)
|
|
| 33 | +- Fixed archive member size writing logic in ``GHC.SysTools.Ar`` (:ghc-ticket:`26120`, :ghc-ticket:`22586`)
|
|
| 34 | + |
|
| 35 | +Runtime System
|
|
| 36 | +~~~~~~~~~~~~~~
|
|
| 37 | + |
|
| 38 | +- Fixed ``MessageBlackHole.link`` to always be a valid closure
|
|
| 39 | +- Fixed handling of WHITEHOLE in ``messageBlackHole`` (:ghc-ticket:`26205`)
|
|
| 40 | +- Fixed ``rts_clearMemory`` logic when sanity checks are enabled (:ghc-ticket:`26011`)
|
|
| 41 | +- Fixed underflow frame lookups in the bytecode interpreter (:ghc-ticket:`25750`)
|
|
| 42 | +- Fixed overflows and reentrancy in interpreter statistics calculation (:ghc-ticket:`25756`)
|
|
| 43 | +- Fixed INTERP_STATS profiling code (:ghc-ticket:`25695`)
|
|
| 44 | +- Removed problematic ``n_free`` variable from nonmovingGC (:ghc-ticket:`26186`)
|
|
| 45 | +- Fixed incorrect format specifiers in era profiling
|
|
| 46 | +- Improved documentation of SLIDE and PACK bytecode instructions
|
|
| 47 | +- Eliminated redundant ``SLIDE x 0`` bytecode instructions
|
|
| 48 | +- Fixed compile issues on powerpc64 ELF v1
|
|
| 49 | + |
|
| 50 | +Code Generation
|
|
| 51 | +~~~~~~~~~~~~~~~
|
|
| 52 | + |
|
| 53 | +- Fixed LLVM built-in variable predicate (was checking ``$llvm`` instead of ``@llvm``)
|
|
| 54 | +- Fixed linkage of built-in arrays for LLVM (:ghc-ticket:`25769`)
|
|
| 55 | +- Fixed code generation for SSE vector operations (:ghc-ticket:`25859`)
|
|
| 56 | +- Fixed ``bswap64`` code generation on i386 (:ghc-ticket:`25601`)
|
|
| 57 | +- Fixed sub-word arithmetic right shift on AArch64 (:ghc-ticket:`26061`)
|
|
| 58 | +- Fixed LLVM vector literal emission to include type information
|
|
| 59 | +- Fixed LLVM version detection
|
|
| 60 | +- Fixed typo in ``padLiveArgs`` that caused segfaults (:ghc-ticket:`25770`, :ghc-ticket:`25773`)
|
|
| 61 | +- Fixed constant-folding for Word->Float bitcasts
|
|
| 62 | +- Added surface syntax for Word/Float bitcast operations
|
|
| 63 | +- Fixed ``MOVD`` format in x86 NCG for ``unpackInt64X2#``
|
|
| 64 | +- Added ``-finter-module-far-jumps`` flag for AArch64
|
|
| 65 | +- Fixed RV64 J instruction handling for non-local jumps (:ghc-ticket:`25738`)
|
|
| 66 | +- Reapplied division by constants optimization
|
|
| 67 | +- Fixed TNTC to set CmmProc entry_label properly (:ghc-ticket:`25565`)
|
|
| 68 | + |
|
| 69 | +Linker
|
|
| 70 | +~~~~~~
|
|
| 71 | + |
|
| 72 | +- Improved efficiency of proddable blocks structure (:ghc-ticket:`26009`)
|
|
| 73 | +- Fixed Windows DLL loading to avoid redundant ``LoadLibraryEx`` calls (:ghc-ticket:`26009`)
|
|
| 74 | +- Fixed incorrect use of ``break`` in nested for loop (:ghc-ticket:`26052`)
|
|
| 75 | +- Fixed linker to not fail due to ``RTLD_NOW`` (:ghc-ticket:`25943`)
|
|
| 76 | +- Dropped obsolete Windows XP compatibility checks
|
|
| 77 | + |
|
| 78 | +GHCi
|
|
| 79 | +~~~~
|
|
| 80 | + |
|
| 81 | +- Fixed ``mkTopLevEnv`` to use ``loadInterfaceForModule`` instead of ``loadSrcInterface`` (:ghc-ticket:`25951`)
|
|
| 82 | + |
|
| 83 | +Template Haskell
|
|
| 84 | +~~~~~~~~~~~~~~~~
|
|
| 85 | + |
|
| 86 | +- Added explicit export lists to all remaining template-haskell modules
|
|
| 87 | + |
|
| 88 | +Build system
|
|
| 89 | +~~~~~~~~~~~~~~~~
|
|
| 90 | + |
|
| 91 | +- Exposed all of Backtraces' internals for ghc-internal (:ghc-ticket:`26049`)
|
|
| 92 | +- Fixed cross-compilation configuration override (:ghc-ticket:`26236`)
|
|
| 16 | 93 | |
| 17 | 94 | Included libraries
|
| 18 | 95 | ~~~~~~~~~~~~~~~~~~
|
| ... | ... | @@ -1725,7 +1725,7 @@ async def do_test(name: TestName, |
| 1725 | 1725 | dst_makefile = in_testdir('Makefile')
|
| 1726 | 1726 | if src_makefile.exists():
|
| 1727 | 1727 | makefile = src_makefile.read_text(encoding='UTF-8')
|
| 1728 | - makefile = re.sub('TOP=.*', 'TOP=%s' % config.top, makefile, 1)
|
|
| 1728 | + makefile = re.sub('TOP=.*', 'TOP=%s' % config.top, makefile, count=1)
|
|
| 1729 | 1729 | dst_makefile.write_text(makefile, encoding='UTF-8')
|
| 1730 | 1730 | |
| 1731 | 1731 | if opts.pre_cmd:
|
| ... | ... | @@ -76,3 +76,7 @@ hypsrcTest: |
| 76 | 76 | .PHONY: haddockForeignTest
|
| 77 | 77 | haddockForeignTest:
|
| 78 | 78 | '$(HADDOCK)' A.hs B.hs F.hs arith.c
|
| 79 | + |
|
| 80 | +.PHONY: T26114
|
|
| 81 | +T26114:
|
|
| 82 | + '$(HADDOCK)' T26114.hs |
| 1 | +{-# LANGUAGE TypeFamilies #-}
|
|
| 2 | + |
|
| 3 | +-- | Module
|
|
| 4 | +module T26114 where
|
|
| 5 | + |
|
| 6 | +-- | C1
|
|
| 7 | +class C1 t where
|
|
| 8 | + type C2 t
|
|
| 9 | + |
|
| 10 | +-- | A
|
|
| 11 | +data A = A
|
|
| 12 | + |
|
| 13 | +instance C1 A where
|
|
| 14 | + type C2 A = B
|
|
| 15 | + |
|
| 16 | +-- | B
|
|
| 17 | +data B = B
|
|
| 18 | + |
|
| 19 | +instance C1 B where
|
|
| 20 | + type C2 B = C
|
|
| 21 | + |
|
| 22 | +-- | C
|
|
| 23 | +data C = C |
| 1 | +[1 of 1] Compiling T26114 ( T26114.hs, nothing )
|
|
| 2 | +Haddock coverage:
|
|
| 3 | + 100% ( 5 / 5) in 'T26114' |
| ... | ... | @@ -24,3 +24,8 @@ test('haddockForeignTest', |
| 24 | 24 | [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'])],
|
| 25 | 25 | makefile_test,
|
| 26 | 26 | ['haddockForeignTest'])
|
| 27 | + |
|
| 28 | +test('T26114',
|
|
| 29 | + [ignore_stderr, req_haddock, extra_files(['T26114.hs'])],
|
|
| 30 | + makefile_test,
|
|
| 31 | + ['T26114']) |
| 1 | 1 | T14172.hs:7:46: error: [GHC-88464]
|
| 2 | - • Found type wildcard ‘_’ standing for ‘a'1 :: k0’
|
|
| 3 | - Where: ‘k0’ is an ambiguous type variable
|
|
| 2 | + • Found type wildcard ‘_’ standing for ‘a'1 :: k30’
|
|
| 3 | + Where: ‘k30’ is an ambiguous type variable
|
|
| 4 | 4 | ‘a'1’ is an ambiguous type variable
|
| 5 | 5 | To use the inferred type, enable PartialTypeSignatures
|
| 6 | 6 | • In the first argument of ‘h’, namely ‘_’
|
| 1 | 1 | ## Changes in 2.32.0
|
| 2 | 2 | * Add highlighting for inline-code-blocks (sections enclosed in @'s)
|
| 3 | 3 | |
| 4 | + * Fix missing documentation for orphan instances from other packages.
|
|
| 5 | + |
|
| 4 | 6 | * Add incremental mode to support rendering documentation one module at a time.
|
| 5 | 7 | |
| 6 | 8 | * The flag `--no-compilation` has been added. This flag causes Haddock to avoid
|
| ... | ... | @@ -93,7 +93,10 @@ attachInstances expInfo ifaces instIfaceMap isOneShot = do |
| 93 | 93 | , fromOrig == Just True || not (null reExp)
|
| 94 | 94 | ]
|
| 95 | 95 | mods_to_load = moduleSetElts mods
|
| 96 | - mods_visible = mkModuleSet $ map ifaceMod ifaces
|
|
| 96 | + -- We need to ensure orphans in modules outside of this package are included.
|
|
| 97 | + -- See https://gitlab.haskell.org/ghc/ghc/-/issues/25147
|
|
| 98 | + -- and https://gitlab.haskell.org/ghc/ghc/-/issues/26079
|
|
| 99 | + mods_visible = mkModuleSet $ concatMap (liftA2 (:) ifaceMod ifaceOrphanDeps) ifaces
|
|
| 97 | 100 | |
| 98 | 101 | (_msgs, mb_index) <- do
|
| 99 | 102 | hsc_env <- getSession
|
| ... | ... | @@ -59,6 +59,7 @@ import GHC.Types.Name.Set |
| 59 | 59 | import GHC.Types.SafeHaskell
|
| 60 | 60 | import qualified GHC.Types.SrcLoc as SrcLoc
|
| 61 | 61 | import qualified GHC.Types.Unique.Map as UniqMap
|
| 62 | +import GHC.Unit.Module.Deps (dep_orphs)
|
|
| 62 | 63 | import GHC.Unit.Module.ModIface
|
| 63 | 64 | import GHC.Unit.State (PackageName (..), UnitState)
|
| 64 | 65 | import GHC.Utils.Outputable (SDocContext)
|
| ... | ... | @@ -270,6 +271,7 @@ createInterface1' flags unit_state dflags hie_file mod_iface ifaces inst_ifaces |
| 270 | 271 | , ifaceVisibleExports = visible_names
|
| 271 | 272 | , ifaceFixMap = fixities
|
| 272 | 273 | , ifaceInstances = instances
|
| 274 | + , ifaceOrphanDeps = dep_orphs $ mi_deps mod_iface
|
|
| 273 | 275 | , ifaceOrphanInstances = [] -- Filled in attachInstances
|
| 274 | 276 | , ifaceRnOrphanInstances = [] -- Filled in renameInterfaceRn
|
| 275 | 277 | , ifaceHaddockCoverage = coverage
|
| ... | ... | @@ -155,6 +155,7 @@ rename sDocContext renamer = rn |
| 155 | 155 | | otherwise = isTermVarOrFieldNameSpace
|
| 156 | 156 | typeNsChoices
|
| 157 | 157 | | isDataOcc occ = isTcClsNameSpace
|
| 158 | + | isSymOcc occ = isTcClsNameSpace
|
|
| 158 | 159 | | otherwise = isTvNameSpace
|
| 159 | 160 | -- Generate the choices for the possible kind of thing this
|
| 160 | 161 | -- is. We narrow down the possibilities with the namespace (if
|
| ... | ... | @@ -104,6 +104,7 @@ renameInterface dflags ignoreSet renamingEnv warnings hoogle iface = do |
| 104 | 104 | && isExternalName name
|
| 105 | 105 | && not (isBuiltInSyntax name)
|
| 106 | 106 | && not (isTyVarName name)
|
| 107 | + && not (isDerivedOccName $ nameOccName name)
|
|
| 107 | 108 | && Exact name /= eqTyCon_RDR
|
| 108 | 109 | -- Must not be in the set of ignored symbols for the module or the
|
| 109 | 110 | -- unqualified ignored symbols
|
| ... | ... | @@ -131,6 +131,9 @@ data Interface = Interface |
| 131 | 131 | -- Names from modules that are entirely re-exported don't count as visible.
|
| 132 | 132 | , ifaceInstances :: [ClsInst]
|
| 133 | 133 | -- ^ Instances exported by the module.
|
| 134 | + , ifaceOrphanDeps :: [Module]
|
|
| 135 | + -- ^ The list of modules to check for orphan instances if this module is
|
|
| 136 | + -- imported.
|
|
| 134 | 137 | , ifaceOrphanInstances :: [DocInstance GhcRn]
|
| 135 | 138 | -- ^ Orphan instances
|
| 136 | 139 | , ifaceRnOrphanInstances :: [DocInstance DocNameI]
|
| 1 | +{-# LANGUAGE LambdaCase #-}
|
|
| 1 | 2 | {-# LANGUAGE OverloadedStrings #-}
|
| 2 | 3 | {-# LANGUAGE ViewPatterns #-}
|
| 3 | 4 | |
| ... | ... | @@ -28,6 +29,7 @@ import Control.Applicative |
| 28 | 29 | import Control.Arrow (first)
|
| 29 | 30 | import Control.Monad
|
| 30 | 31 | import Data.Char (chr, isAlpha, isSpace, isUpper)
|
| 32 | +import Data.Functor (($>))
|
|
| 31 | 33 | import Data.List (elemIndex, intercalate, intersperse, unfoldr)
|
| 32 | 34 | import Data.Maybe (fromMaybe, mapMaybe)
|
| 33 | 35 | import Data.Monoid
|
| ... | ... | @@ -186,11 +188,29 @@ specialChar = "_/<@\"&'`#[ " |
| 186 | 188 | -- to ensure that we have already given a chance to more meaningful parsers
|
| 187 | 189 | -- before capturing their characters.
|
| 188 | 190 | string' :: Parser (DocH mod a)
|
| 189 | -string' = DocString . unescape . T.unpack <$> takeWhile1_ (`notElem` specialChar)
|
|
| 191 | +string' =
|
|
| 192 | + DocString
|
|
| 193 | + <$> ((:) <$> rawOrEscChar "" <*> many (rawOrEscChar "(["))
|
|
| 194 | + -- After the first character, stop for @\(@ or @\[@ math starters. (The
|
|
| 195 | + -- first character won't start a valid math string because this parser
|
|
| 196 | + -- should follow math parsers. But this parser is expected to accept at
|
|
| 197 | + -- least one character from all inputs that don't start with special
|
|
| 198 | + -- characters, so the first character parser can't have the @"(["@
|
|
| 199 | + -- restriction.)
|
|
| 190 | 200 | where
|
| 191 | - unescape "" = ""
|
|
| 192 | - unescape ('\\' : x : xs) = x : unescape xs
|
|
| 193 | - unescape (x : xs) = x : unescape xs
|
|
| 201 | + -- | Parse a single logical character, either raw or escaped. Don't accept
|
|
| 202 | + -- escaped characters from the argument string.
|
|
| 203 | + rawOrEscChar :: [Char] -> Parser Char
|
|
| 204 | + rawOrEscChar restrictedEscapes = try $ Parsec.noneOf specialChar >>= \case
|
|
| 205 | + -- Handle backslashes:
|
|
| 206 | + -- - Fail on forbidden escape characters.
|
|
| 207 | + -- - Non-forbidden characters: simply unescape, e.g. parse "\b" as 'b',
|
|
| 208 | + -- - Trailing backslash: treat it as a raw backslash, not an escape
|
|
| 209 | + -- sequence. (This is the logic that this parser followed when this
|
|
| 210 | + -- comment was written; it is not necessarily intentional but now I
|
|
| 211 | + -- don't want to break anything relying on it.)
|
|
| 212 | + '\\' -> Parsec.noneOf restrictedEscapes <|> Parsec.eof $> '\\'
|
|
| 213 | + c -> pure c
|
|
| 194 | 214 | |
| 195 | 215 | -- | Skips a single special character and treats it as a plain string.
|
| 196 | 216 | -- This is done to skip over any special characters belonging to other
|
| ... | ... | @@ -795,31 +815,33 @@ stripSpace = fromMaybe <*> mapM strip' |
| 795 | 815 | -- | Parses examples. Examples are a paragraph level entity (separated by an empty line).
|
| 796 | 816 | -- Consecutive examples are accepted.
|
| 797 | 817 | examples :: Parser (DocH mod a)
|
| 798 | -examples = DocExamples <$> (many (try (skipHorizontalSpace *> "\n")) *> go)
|
|
| 818 | +examples = DocExamples <$> (many (try (skipHorizontalSpace *> "\n")) *> go Nothing)
|
|
| 799 | 819 | where
|
| 800 | - go :: Parser [Example]
|
|
| 801 | - go = do
|
|
| 820 | + go :: Maybe Text -> Parser [Example]
|
|
| 821 | + go mbInitialIndent = do
|
|
| 802 | 822 | prefix <- takeHorizontalSpace <* ">>>"
|
| 823 | + initialIndent <- maybe takeHorizontalSpace pure mbInitialIndent
|
|
| 803 | 824 | expr <- takeLine
|
| 804 | - (rs, es) <- resultAndMoreExamples
|
|
| 805 | - return (makeExample prefix expr rs : es)
|
|
| 825 | + (rs, es) <- resultAndMoreExamples (Just initialIndent)
|
|
| 826 | + return (makeExample prefix initialIndent expr rs : es)
|
|
| 827 | + |
|
| 828 | + resultAndMoreExamples :: Maybe Text -> Parser ([Text], [Example])
|
|
| 829 | + resultAndMoreExamples mbInitialIndent = choice' [moreExamples, result, pure ([], [])]
|
|
| 806 | 830 | where
|
| 807 | - resultAndMoreExamples :: Parser ([Text], [Example])
|
|
| 808 | - resultAndMoreExamples = choice' [moreExamples, result, pure ([], [])]
|
|
| 809 | - where
|
|
| 810 | - moreExamples :: Parser ([Text], [Example])
|
|
| 811 | - moreExamples = (,) [] <$> go
|
|
| 831 | + moreExamples :: Parser ([Text], [Example])
|
|
| 832 | + moreExamples = (,) [] <$> go mbInitialIndent
|
|
| 812 | 833 | |
| 813 | - result :: Parser ([Text], [Example])
|
|
| 814 | - result = first . (:) <$> nonEmptyLine <*> resultAndMoreExamples
|
|
| 834 | + result :: Parser ([Text], [Example])
|
|
| 835 | + result = first . (:) <$> nonEmptyLine <*> resultAndMoreExamples Nothing
|
|
| 815 | 836 | |
| 816 | - makeExample :: Text -> Text -> [Text] -> Example
|
|
| 817 | - makeExample prefix expression res =
|
|
| 818 | - Example (T.unpack (T.strip expression)) result
|
|
| 837 | + makeExample :: Text -> Text -> Text -> [Text] -> Example
|
|
| 838 | + makeExample prefix indent expression res =
|
|
| 839 | + Example (T.unpack (tryStripIndent (T.stripEnd expression))) result
|
|
| 819 | 840 | where
|
| 820 | 841 | result = map (T.unpack . substituteBlankLine . tryStripPrefix) res
|
| 821 | 842 | |
| 822 | 843 | tryStripPrefix xs = fromMaybe xs (T.stripPrefix prefix xs)
|
| 844 | + tryStripIndent = liftA2 fromMaybe T.stripStart (T.stripPrefix indent)
|
|
| 823 | 845 | |
| 824 | 846 | substituteBlankLine "<BLANKLINE>" = ""
|
| 825 | 847 | substituteBlankLine xs = xs
|
| ... | ... | @@ -284,6 +284,13 @@ spec = do |
| 284 | 284 | it "supports title for deprecated picture syntax" $ do
|
| 285 | 285 | "<<b a z>>" `shouldParseTo` image "b" "a z"
|
| 286 | 286 | |
| 287 | + context "when parsing inline math" $ do
|
|
| 288 | + it "accepts inline math immediately after punctuation" $ do
|
|
| 289 | + "(\\(1 + 2 = 3\\) is an example of addition)"
|
|
| 290 | + `shouldParseTo` "("
|
|
| 291 | + <> DocMathInline "1 + 2 = 3"
|
|
| 292 | + <> " is an example of addition)"
|
|
| 293 | + |
|
| 287 | 294 | context "when parsing display math" $ do
|
| 288 | 295 | it "accepts markdown syntax for display math containing newlines" $ do
|
| 289 | 296 | "\\[\\pi\n\\pi\\]" `shouldParseTo` DocMathDisplay "\\pi\n\\pi"
|
| ... | ... | @@ -864,6 +871,29 @@ spec = do |
| 864 | 871 | it "accepts unicode in examples" $ do
|
| 865 | 872 | ">>> 灼眼\nシャナ" `shouldParseTo` DocExamples [Example "灼眼" ["シャナ"]]
|
| 866 | 873 | |
| 874 | + it "preserves indentation in consecutive example lines" $ do
|
|
| 875 | + unlines
|
|
| 876 | + [ ">>> line 1"
|
|
| 877 | + , ">>> line 2"
|
|
| 878 | + , ">>> line 3"
|
|
| 879 | + ]
|
|
| 880 | + `shouldParseTo` DocExamples
|
|
| 881 | + [ Example "line 1" []
|
|
| 882 | + , Example " line 2" []
|
|
| 883 | + , Example "line 3" []
|
|
| 884 | + ]
|
|
| 885 | + |
|
| 886 | + it "resets indentation after results" $ do
|
|
| 887 | + unlines
|
|
| 888 | + [ ">>> line 1"
|
|
| 889 | + , "result"
|
|
| 890 | + , ">>> line 2"
|
|
| 891 | + ]
|
|
| 892 | + `shouldParseTo` DocExamples
|
|
| 893 | + [ Example "line 1" ["result"]
|
|
| 894 | + , Example "line 2" []
|
|
| 895 | + ]
|
|
| 896 | + |
|
| 867 | 897 | context "when prompt is prefixed by whitespace" $ do
|
| 868 | 898 | it "strips the exact same amount of whitespace from result lines" $ do
|
| 869 | 899 | unlines
|
| ... | ... | @@ -262,6 +262,7 @@ baseDependencies ghcPath = do |
| 262 | 262 | pkgs =
|
| 263 | 263 | [ "array"
|
| 264 | 264 | , "base"
|
| 265 | + , "deepseq"
|
|
| 265 | 266 | , "ghc-prim"
|
| 266 | 267 | , "process"
|
| 267 | 268 | , "template-haskell"
|
| ... | ... | @@ -797,7 +797,61 @@ |
| 797 | 797 | ><tr
|
| 798 | 798 | ><td class="src clearfix"
|
| 799 | 799 | ><span class="inst-left"
|
| 800 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Alternative:8"
|
|
| 800 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:NFData1:8"
|
|
| 801 | + ></span
|
|
| 802 | + > <span class="breakable"
|
|
| 803 | + >(<span class="unbreakable"
|
|
| 804 | + ><a href="#" title="Control.DeepSeq"
|
|
| 805 | + >NFData1</a
|
|
| 806 | + > f</span
|
|
| 807 | + >, <span class="unbreakable"
|
|
| 808 | + ><a href="#" title="Control.DeepSeq"
|
|
| 809 | + >NFData1</a
|
|
| 810 | + > g</span
|
|
| 811 | + >)</span
|
|
| 812 | + > => <a href="#" title="Control.DeepSeq"
|
|
| 813 | + >NFData1</a
|
|
| 814 | + > (<a href="#" title="Bug1004"
|
|
| 815 | + >Product</a
|
|
| 816 | + > f g)</span
|
|
| 817 | + > <a href="#" class="selflink"
|
|
| 818 | + >#</a
|
|
| 819 | + ></td
|
|
| 820 | + ><td class="doc"
|
|
| 821 | + ><p
|
|
| 822 | + ><em
|
|
| 823 | + >Since: deepseq-1.4.3.0</em
|
|
| 824 | + ></p
|
|
| 825 | + ></td
|
|
| 826 | + ></tr
|
|
| 827 | + ><tr
|
|
| 828 | + ><td colspan="2"
|
|
| 829 | + ><details id="i:id:Product:NFData1:8"
|
|
| 830 | + ><summary class="hide-when-js-enabled"
|
|
| 831 | + >Instance details</summary
|
|
| 832 | + ><p
|
|
| 833 | + >Defined in <a href="#"
|
|
| 834 | + >Control.DeepSeq</a
|
|
| 835 | + ></p
|
|
| 836 | + > <div class="subs methods"
|
|
| 837 | + ><p class="caption"
|
|
| 838 | + >Methods</p
|
|
| 839 | + ><p class="src"
|
|
| 840 | + ><a href="#"
|
|
| 841 | + >liftRnf</a
|
|
| 842 | + > :: (a -> ()) -> <a href="#" title="Bug1004"
|
|
| 843 | + >Product</a
|
|
| 844 | + > f g a -> () <a href="#" class="selflink"
|
|
| 845 | + >#</a
|
|
| 846 | + ></p
|
|
| 847 | + ></div
|
|
| 848 | + ></details
|
|
| 849 | + ></td
|
|
| 850 | + ></tr
|
|
| 851 | + ><tr
|
|
| 852 | + ><td class="src clearfix"
|
|
| 853 | + ><span class="inst-left"
|
|
| 854 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Alternative:9"
|
|
| 801 | 855 | ></span
|
| 802 | 856 | > (<a href="#" title="Control.Applicative"
|
| 803 | 857 | >Alternative</a
|
| ... | ... | @@ -820,7 +874,7 @@ |
| 820 | 874 | ></tr
|
| 821 | 875 | ><tr
|
| 822 | 876 | ><td colspan="2"
|
| 823 | - ><details id="i:id:Product:Alternative:8"
|
|
| 877 | + ><details id="i:id:Product:Alternative:9"
|
|
| 824 | 878 | ><summary class="hide-when-js-enabled"
|
| 825 | 879 | >Instance details</summary
|
| 826 | 880 | ><p
|
| ... | ... | @@ -877,7 +931,7 @@ |
| 877 | 931 | ><tr
|
| 878 | 932 | ><td class="src clearfix"
|
| 879 | 933 | ><span class="inst-left"
|
| 880 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Applicative:9"
|
|
| 934 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Applicative:10"
|
|
| 881 | 935 | ></span
|
| 882 | 936 | > (<a href="#" title="Control.Applicative"
|
| 883 | 937 | >Applicative</a
|
| ... | ... | @@ -900,7 +954,7 @@ |
| 900 | 954 | ></tr
|
| 901 | 955 | ><tr
|
| 902 | 956 | ><td colspan="2"
|
| 903 | - ><details id="i:id:Product:Applicative:9"
|
|
| 957 | + ><details id="i:id:Product:Applicative:10"
|
|
| 904 | 958 | ><summary class="hide-when-js-enabled"
|
| 905 | 959 | >Instance details</summary
|
| 906 | 960 | ><p
|
| ... | ... | @@ -973,7 +1027,7 @@ |
| 973 | 1027 | ><tr
|
| 974 | 1028 | ><td class="src clearfix"
|
| 975 | 1029 | ><span class="inst-left"
|
| 976 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Functor:10"
|
|
| 1030 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Functor:11"
|
|
| 977 | 1031 | ></span
|
| 978 | 1032 | > (<a href="#" title="Control.Monad"
|
| 979 | 1033 | >Functor</a
|
| ... | ... | @@ -996,7 +1050,7 @@ |
| 996 | 1050 | ></tr
|
| 997 | 1051 | ><tr
|
| 998 | 1052 | ><td colspan="2"
|
| 999 | - ><details id="i:id:Product:Functor:10"
|
|
| 1053 | + ><details id="i:id:Product:Functor:11"
|
|
| 1000 | 1054 | ><summary class="hide-when-js-enabled"
|
| 1001 | 1055 | >Instance details</summary
|
| 1002 | 1056 | ><p
|
| ... | ... | @@ -1033,7 +1087,7 @@ |
| 1033 | 1087 | ><tr
|
| 1034 | 1088 | ><td class="src clearfix"
|
| 1035 | 1089 | ><span class="inst-left"
|
| 1036 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Monad:11"
|
|
| 1090 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Monad:12"
|
|
| 1037 | 1091 | ></span
|
| 1038 | 1092 | > (<a href="#" title="Control.Monad"
|
| 1039 | 1093 | >Monad</a
|
| ... | ... | @@ -1056,7 +1110,7 @@ |
| 1056 | 1110 | ></tr
|
| 1057 | 1111 | ><tr
|
| 1058 | 1112 | ><td colspan="2"
|
| 1059 | - ><details id="i:id:Product:Monad:11"
|
|
| 1113 | + ><details id="i:id:Product:Monad:12"
|
|
| 1060 | 1114 | ><summary class="hide-when-js-enabled"
|
| 1061 | 1115 | >Instance details</summary
|
| 1062 | 1116 | ><p
|
| ... | ... | @@ -1105,7 +1159,7 @@ |
| 1105 | 1159 | ><tr
|
| 1106 | 1160 | ><td class="src clearfix"
|
| 1107 | 1161 | ><span class="inst-left"
|
| 1108 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadPlus:12"
|
|
| 1162 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadPlus:13"
|
|
| 1109 | 1163 | ></span
|
| 1110 | 1164 | > (<a href="#" title="Control.Monad"
|
| 1111 | 1165 | >MonadPlus</a
|
| ... | ... | @@ -1128,7 +1182,7 @@ |
| 1128 | 1182 | ></tr
|
| 1129 | 1183 | ><tr
|
| 1130 | 1184 | ><td colspan="2"
|
| 1131 | - ><details id="i:id:Product:MonadPlus:12"
|
|
| 1185 | + ><details id="i:id:Product:MonadPlus:13"
|
|
| 1132 | 1186 | ><summary class="hide-when-js-enabled"
|
| 1133 | 1187 | >Instance details</summary
|
| 1134 | 1188 | ><p
|
| ... | ... | @@ -1165,7 +1219,7 @@ |
| 1165 | 1219 | ><tr
|
| 1166 | 1220 | ><td class="src clearfix"
|
| 1167 | 1221 | ><span class="inst-left"
|
| 1168 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadFix:13"
|
|
| 1222 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadFix:14"
|
|
| 1169 | 1223 | ></span
|
| 1170 | 1224 | > (<a href="#" title="Control.Monad.Fix"
|
| 1171 | 1225 | >MonadFix</a
|
| ... | ... | @@ -1188,7 +1242,7 @@ |
| 1188 | 1242 | ></tr
|
| 1189 | 1243 | ><tr
|
| 1190 | 1244 | ><td colspan="2"
|
| 1191 | - ><details id="i:id:Product:MonadFix:13"
|
|
| 1245 | + ><details id="i:id:Product:MonadFix:14"
|
|
| 1192 | 1246 | ><summary class="hide-when-js-enabled"
|
| 1193 | 1247 | >Instance details</summary
|
| 1194 | 1248 | ><p
|
| ... | ... | @@ -1215,7 +1269,7 @@ |
| 1215 | 1269 | ><tr
|
| 1216 | 1270 | ><td class="src clearfix"
|
| 1217 | 1271 | ><span class="inst-left"
|
| 1218 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadZip:14"
|
|
| 1272 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:MonadZip:15"
|
|
| 1219 | 1273 | ></span
|
| 1220 | 1274 | > (<a href="#" title="Control.Monad.Zip"
|
| 1221 | 1275 | >MonadZip</a
|
| ... | ... | @@ -1238,7 +1292,7 @@ |
| 1238 | 1292 | ></tr
|
| 1239 | 1293 | ><tr
|
| 1240 | 1294 | ><td colspan="2"
|
| 1241 | - ><details id="i:id:Product:MonadZip:14"
|
|
| 1295 | + ><details id="i:id:Product:MonadZip:15"
|
|
| 1242 | 1296 | ><summary class="hide-when-js-enabled"
|
| 1243 | 1297 | >Instance details</summary
|
| 1244 | 1298 | ><p
|
| ... | ... | @@ -1291,7 +1345,7 @@ |
| 1291 | 1345 | ><tr
|
| 1292 | 1346 | ><td class="src clearfix"
|
| 1293 | 1347 | ><span class="inst-left"
|
| 1294 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Foldable:15"
|
|
| 1348 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Foldable:16"
|
|
| 1295 | 1349 | ></span
|
| 1296 | 1350 | > (<a href="#" title="Data.Foldable"
|
| 1297 | 1351 | >Foldable</a
|
| ... | ... | @@ -1314,7 +1368,7 @@ |
| 1314 | 1368 | ></tr
|
| 1315 | 1369 | ><tr
|
| 1316 | 1370 | ><td colspan="2"
|
| 1317 | - ><details id="i:id:Product:Foldable:15"
|
|
| 1371 | + ><details id="i:id:Product:Foldable:16"
|
|
| 1318 | 1372 | ><summary class="hide-when-js-enabled"
|
| 1319 | 1373 | >Instance details</summary
|
| 1320 | 1374 | ><p
|
| ... | ... | @@ -1489,7 +1543,7 @@ |
| 1489 | 1543 | ><tr
|
| 1490 | 1544 | ><td class="src clearfix"
|
| 1491 | 1545 | ><span class="inst-left"
|
| 1492 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Traversable:16"
|
|
| 1546 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Traversable:17"
|
|
| 1493 | 1547 | ></span
|
| 1494 | 1548 | > (<a href="#" title="Data.Traversable"
|
| 1495 | 1549 | >Traversable</a
|
| ... | ... | @@ -1512,7 +1566,7 @@ |
| 1512 | 1566 | ></tr
|
| 1513 | 1567 | ><tr
|
| 1514 | 1568 | ><td colspan="2"
|
| 1515 | - ><details id="i:id:Product:Traversable:16"
|
|
| 1569 | + ><details id="i:id:Product:Traversable:17"
|
|
| 1516 | 1570 | ><summary class="hide-when-js-enabled"
|
| 1517 | 1571 | >Instance details</summary
|
| 1518 | 1572 | ><p
|
| ... | ... | @@ -1577,7 +1631,65 @@ |
| 1577 | 1631 | ><tr
|
| 1578 | 1632 | ><td class="src clearfix"
|
| 1579 | 1633 | ><span class="inst-left"
|
| 1580 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Monoid:17"
|
|
| 1634 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:NFData:18"
|
|
| 1635 | + ></span
|
|
| 1636 | + > <span class="breakable"
|
|
| 1637 | + >(<span class="unbreakable"
|
|
| 1638 | + ><a href="#" title="Control.DeepSeq"
|
|
| 1639 | + >NFData</a
|
|
| 1640 | + > (f a)</span
|
|
| 1641 | + >, <span class="unbreakable"
|
|
| 1642 | + ><a href="#" title="Control.DeepSeq"
|
|
| 1643 | + >NFData</a
|
|
| 1644 | + > (g a)</span
|
|
| 1645 | + >)</span
|
|
| 1646 | + > => <a href="#" title="Control.DeepSeq"
|
|
| 1647 | + >NFData</a
|
|
| 1648 | + > (<a href="#" title="Bug1004"
|
|
| 1649 | + >Product</a
|
|
| 1650 | + > f g a)</span
|
|
| 1651 | + > <a href="#" class="selflink"
|
|
| 1652 | + >#</a
|
|
| 1653 | + ></td
|
|
| 1654 | + ><td class="doc"
|
|
| 1655 | + ><p
|
|
| 1656 | + >Note: in <code class="inline-code"
|
|
| 1657 | + >deepseq-1.5.0.0</code
|
|
| 1658 | + > this instance's superclasses were changed.</p
|
|
| 1659 | + ><p
|
|
| 1660 | + ><em
|
|
| 1661 | + >Since: deepseq-1.4.3.0</em
|
|
| 1662 | + ></p
|
|
| 1663 | + ></td
|
|
| 1664 | + ></tr
|
|
| 1665 | + ><tr
|
|
| 1666 | + ><td colspan="2"
|
|
| 1667 | + ><details id="i:id:Product:NFData:18"
|
|
| 1668 | + ><summary class="hide-when-js-enabled"
|
|
| 1669 | + >Instance details</summary
|
|
| 1670 | + ><p
|
|
| 1671 | + >Defined in <a href="#"
|
|
| 1672 | + >Control.DeepSeq</a
|
|
| 1673 | + ></p
|
|
| 1674 | + > <div class="subs methods"
|
|
| 1675 | + ><p class="caption"
|
|
| 1676 | + >Methods</p
|
|
| 1677 | + ><p class="src"
|
|
| 1678 | + ><a href="#"
|
|
| 1679 | + >rnf</a
|
|
| 1680 | + > :: <a href="#" title="Bug1004"
|
|
| 1681 | + >Product</a
|
|
| 1682 | + > f g a -> () <a href="#" class="selflink"
|
|
| 1683 | + >#</a
|
|
| 1684 | + ></p
|
|
| 1685 | + ></div
|
|
| 1686 | + ></details
|
|
| 1687 | + ></td
|
|
| 1688 | + ></tr
|
|
| 1689 | + ><tr
|
|
| 1690 | + ><td class="src clearfix"
|
|
| 1691 | + ><span class="inst-left"
|
|
| 1692 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Monoid:19"
|
|
| 1581 | 1693 | ></span
|
| 1582 | 1694 | > (<a href="#" title="Data.Monoid"
|
| 1583 | 1695 | >Monoid</a
|
| ... | ... | @@ -1600,7 +1712,7 @@ |
| 1600 | 1712 | ></tr
|
| 1601 | 1713 | ><tr
|
| 1602 | 1714 | ><td colspan="2"
|
| 1603 | - ><details id="i:id:Product:Monoid:17"
|
|
| 1715 | + ><details id="i:id:Product:Monoid:19"
|
|
| 1604 | 1716 | ><summary class="hide-when-js-enabled"
|
| 1605 | 1717 | >Instance details</summary
|
| 1606 | 1718 | ><p
|
| ... | ... | @@ -1647,7 +1759,7 @@ |
| 1647 | 1759 | ><tr
|
| 1648 | 1760 | ><td class="src clearfix"
|
| 1649 | 1761 | ><span class="inst-left"
|
| 1650 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Semigroup:18"
|
|
| 1762 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Semigroup:20"
|
|
| 1651 | 1763 | ></span
|
| 1652 | 1764 | > (<a href="#" title="Prelude"
|
| 1653 | 1765 | >Semigroup</a
|
| ... | ... | @@ -1670,7 +1782,7 @@ |
| 1670 | 1782 | ></tr
|
| 1671 | 1783 | ><tr
|
| 1672 | 1784 | ><td colspan="2"
|
| 1673 | - ><details id="i:id:Product:Semigroup:18"
|
|
| 1785 | + ><details id="i:id:Product:Semigroup:20"
|
|
| 1674 | 1786 | ><summary class="hide-when-js-enabled"
|
| 1675 | 1787 | >Instance details</summary
|
| 1676 | 1788 | ><p
|
| ... | ... | @@ -1723,21 +1835,235 @@ |
| 1723 | 1835 | ><tr
|
| 1724 | 1836 | ><td class="src clearfix"
|
| 1725 | 1837 | ><span class="inst-left"
|
| 1726 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Data:19"
|
|
| 1838 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Eq:21"
|
|
| 1727 | 1839 | ></span
|
| 1728 | - > (<a href="#" title="Data.Dynamic"
|
|
| 1729 | - >Typeable</a
|
|
| 1730 | - > a, <a href="#" title="Data.Dynamic"
|
|
| 1731 | - >Typeable</a
|
|
| 1732 | - > f, <a href="#" title="Data.Dynamic"
|
|
| 1733 | - >Typeable</a
|
|
| 1734 | - > g, <a href="#" title="Data.Dynamic"
|
|
| 1735 | - >Typeable</a
|
|
| 1736 | - > k, <a href="#" title="Data.Data"
|
|
| 1737 | - >Data</a
|
|
| 1738 | - > (f a), <a href="#" title="Data.Data"
|
|
| 1739 | - >Data</a
|
|
| 1740 | - > (g a)) => <a href="#" title="Data.Data"
|
|
| 1840 | + > <span class="breakable"
|
|
| 1841 | + >(<span class="unbreakable"
|
|
| 1842 | + ><a href="#" title="Data.Eq"
|
|
| 1843 | + >Eq</a
|
|
| 1844 | + > (f a)</span
|
|
| 1845 | + >, <span class="unbreakable"
|
|
| 1846 | + ><a href="#" title="Data.Eq"
|
|
| 1847 | + >Eq</a
|
|
| 1848 | + > (g a)</span
|
|
| 1849 | + >)</span
|
|
| 1850 | + > => <a href="#" title="Data.Eq"
|
|
| 1851 | + >Eq</a
|
|
| 1852 | + > (<a href="#" title="Bug1004"
|
|
| 1853 | + >Product</a
|
|
| 1854 | + > f g a)</span
|
|
| 1855 | + > <a href="#" class="selflink"
|
|
| 1856 | + >#</a
|
|
| 1857 | + ></td
|
|
| 1858 | + ><td class="doc"
|
|
| 1859 | + ><p
|
|
| 1860 | + ><em
|
|
| 1861 | + >Since: base-4.18.0.0</em
|
|
| 1862 | + ></p
|
|
| 1863 | + ></td
|
|
| 1864 | + ></tr
|
|
| 1865 | + ><tr
|
|
| 1866 | + ><td colspan="2"
|
|
| 1867 | + ><details id="i:id:Product:Eq:21"
|
|
| 1868 | + ><summary class="hide-when-js-enabled"
|
|
| 1869 | + >Instance details</summary
|
|
| 1870 | + ><p
|
|
| 1871 | + >Defined in <a href="#"
|
|
| 1872 | + >Data.Functor.Product</a
|
|
| 1873 | + ></p
|
|
| 1874 | + > <div class="subs methods"
|
|
| 1875 | + ><p class="caption"
|
|
| 1876 | + >Methods</p
|
|
| 1877 | + ><p class="src"
|
|
| 1878 | + ><a href="#"
|
|
| 1879 | + >(==)</a
|
|
| 1880 | + > :: <a href="#" title="Bug1004"
|
|
| 1881 | + >Product</a
|
|
| 1882 | + > f g a -> <a href="#" title="Bug1004"
|
|
| 1883 | + >Product</a
|
|
| 1884 | + > f g a -> <a href="#" title="Data.Bool"
|
|
| 1885 | + >Bool</a
|
|
| 1886 | + > <a href="#" class="selflink"
|
|
| 1887 | + >#</a
|
|
| 1888 | + ></p
|
|
| 1889 | + ><p class="src"
|
|
| 1890 | + ><a href="#"
|
|
| 1891 | + >(/=)</a
|
|
| 1892 | + > :: <a href="#" title="Bug1004"
|
|
| 1893 | + >Product</a
|
|
| 1894 | + > f g a -> <a href="#" title="Bug1004"
|
|
| 1895 | + >Product</a
|
|
| 1896 | + > f g a -> <a href="#" title="Data.Bool"
|
|
| 1897 | + >Bool</a
|
|
| 1898 | + > <a href="#" class="selflink"
|
|
| 1899 | + >#</a
|
|
| 1900 | + ></p
|
|
| 1901 | + ></div
|
|
| 1902 | + ></details
|
|
| 1903 | + ></td
|
|
| 1904 | + ></tr
|
|
| 1905 | + ><tr
|
|
| 1906 | + ><td class="src clearfix"
|
|
| 1907 | + ><span class="inst-left"
|
|
| 1908 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Ord:22"
|
|
| 1909 | + ></span
|
|
| 1910 | + > <span class="breakable"
|
|
| 1911 | + >(<span class="unbreakable"
|
|
| 1912 | + ><a href="#" title="Data.Ord"
|
|
| 1913 | + >Ord</a
|
|
| 1914 | + > (f a)</span
|
|
| 1915 | + >, <span class="unbreakable"
|
|
| 1916 | + ><a href="#" title="Data.Ord"
|
|
| 1917 | + >Ord</a
|
|
| 1918 | + > (g a)</span
|
|
| 1919 | + >)</span
|
|
| 1920 | + > => <a href="#" title="Data.Ord"
|
|
| 1921 | + >Ord</a
|
|
| 1922 | + > (<a href="#" title="Bug1004"
|
|
| 1923 | + >Product</a
|
|
| 1924 | + > f g a)</span
|
|
| 1925 | + > <a href="#" class="selflink"
|
|
| 1926 | + >#</a
|
|
| 1927 | + ></td
|
|
| 1928 | + ><td class="doc"
|
|
| 1929 | + ><p
|
|
| 1930 | + ><em
|
|
| 1931 | + >Since: base-4.18.0.0</em
|
|
| 1932 | + ></p
|
|
| 1933 | + ></td
|
|
| 1934 | + ></tr
|
|
| 1935 | + ><tr
|
|
| 1936 | + ><td colspan="2"
|
|
| 1937 | + ><details id="i:id:Product:Ord:22"
|
|
| 1938 | + ><summary class="hide-when-js-enabled"
|
|
| 1939 | + >Instance details</summary
|
|
| 1940 | + ><p
|
|
| 1941 | + >Defined in <a href="#"
|
|
| 1942 | + >Data.Functor.Product</a
|
|
| 1943 | + ></p
|
|
| 1944 | + > <div class="subs methods"
|
|
| 1945 | + ><p class="caption"
|
|
| 1946 | + >Methods</p
|
|
| 1947 | + ><p class="src"
|
|
| 1948 | + ><a href="#"
|
|
| 1949 | + >compare</a
|
|
| 1950 | + > :: <a href="#" title="Bug1004"
|
|
| 1951 | + >Product</a
|
|
| 1952 | + > f g a -> <a href="#" title="Bug1004"
|
|
| 1953 | + >Product</a
|
|
| 1954 | + > f g a -> <a href="#" title="Data.Ord"
|
|
| 1955 | + >Ordering</a
|
|
| 1956 | + > <a href="#" class="selflink"
|
|
| 1957 | + >#</a
|
|
| 1958 | + ></p
|
|
| 1959 | + ><p class="src"
|
|
| 1960 | + ><a href="#"
|
|
| 1961 | + >(<)</a
|
|
| 1962 | + > :: <a href="#" title="Bug1004"
|
|
| 1963 | + >Product</a
|
|
| 1964 | + > f g a -> <a href="#" title="Bug1004"
|
|
| 1965 | + >Product</a
|
|
| 1966 | + > f g a -> <a href="#" title="Data.Bool"
|
|
| 1967 | + >Bool</a
|
|
| 1968 | + > <a href="#" class="selflink"
|
|
| 1969 | + >#</a
|
|
| 1970 | + ></p
|
|
| 1971 | + ><p class="src"
|
|
| 1972 | + ><a href="#"
|
|
| 1973 | + >(<=)</a
|
|
| 1974 | + > :: <a href="#" title="Bug1004"
|
|
| 1975 | + >Product</a
|
|
| 1976 | + > f g a -> <a href="#" title="Bug1004"
|
|
| 1977 | + >Product</a
|
|
| 1978 | + > f g a -> <a href="#" title="Data.Bool"
|
|
| 1979 | + >Bool</a
|
|
| 1980 | + > <a href="#" class="selflink"
|
|
| 1981 | + >#</a
|
|
| 1982 | + ></p
|
|
| 1983 | + ><p class="src"
|
|
| 1984 | + ><a href="#"
|
|
| 1985 | + >(>)</a
|
|
| 1986 | + > :: <a href="#" title="Bug1004"
|
|
| 1987 | + >Product</a
|
|
| 1988 | + > f g a -> <a href="#" title="Bug1004"
|
|
| 1989 | + >Product</a
|
|
| 1990 | + > f g a -> <a href="#" title="Data.Bool"
|
|
| 1991 | + >Bool</a
|
|
| 1992 | + > <a href="#" class="selflink"
|
|
| 1993 | + >#</a
|
|
| 1994 | + ></p
|
|
| 1995 | + ><p class="src"
|
|
| 1996 | + ><a href="#"
|
|
| 1997 | + >(>=)</a
|
|
| 1998 | + > :: <a href="#" title="Bug1004"
|
|
| 1999 | + >Product</a
|
|
| 2000 | + > f g a -> <a href="#" title="Bug1004"
|
|
| 2001 | + >Product</a
|
|
| 2002 | + > f g a -> <a href="#" title="Data.Bool"
|
|
| 2003 | + >Bool</a
|
|
| 2004 | + > <a href="#" class="selflink"
|
|
| 2005 | + >#</a
|
|
| 2006 | + ></p
|
|
| 2007 | + ><p class="src"
|
|
| 2008 | + ><a href="#"
|
|
| 2009 | + >max</a
|
|
| 2010 | + > :: <a href="#" title="Bug1004"
|
|
| 2011 | + >Product</a
|
|
| 2012 | + > f g a -> <a href="#" title="Bug1004"
|
|
| 2013 | + >Product</a
|
|
| 2014 | + > f g a -> <a href="#" title="Bug1004"
|
|
| 2015 | + >Product</a
|
|
| 2016 | + > f g a <a href="#" class="selflink"
|
|
| 2017 | + >#</a
|
|
| 2018 | + ></p
|
|
| 2019 | + ><p class="src"
|
|
| 2020 | + ><a href="#"
|
|
| 2021 | + >min</a
|
|
| 2022 | + > :: <a href="#" title="Bug1004"
|
|
| 2023 | + >Product</a
|
|
| 2024 | + > f g a -> <a href="#" title="Bug1004"
|
|
| 2025 | + >Product</a
|
|
| 2026 | + > f g a -> <a href="#" title="Bug1004"
|
|
| 2027 | + >Product</a
|
|
| 2028 | + > f g a <a href="#" class="selflink"
|
|
| 2029 | + >#</a
|
|
| 2030 | + ></p
|
|
| 2031 | + ></div
|
|
| 2032 | + ></details
|
|
| 2033 | + ></td
|
|
| 2034 | + ></tr
|
|
| 2035 | + ><tr
|
|
| 2036 | + ><td class="src clearfix"
|
|
| 2037 | + ><span class="inst-left"
|
|
| 2038 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Data:23"
|
|
| 2039 | + ></span
|
|
| 2040 | + > <span class="breakable"
|
|
| 2041 | + >(<span class="unbreakable"
|
|
| 2042 | + ><a href="#" title="Data.Dynamic"
|
|
| 2043 | + >Typeable</a
|
|
| 2044 | + > a</span
|
|
| 2045 | + >, <span class="unbreakable"
|
|
| 2046 | + ><a href="#" title="Data.Dynamic"
|
|
| 2047 | + >Typeable</a
|
|
| 2048 | + > f</span
|
|
| 2049 | + >, <span class="unbreakable"
|
|
| 2050 | + ><a href="#" title="Data.Dynamic"
|
|
| 2051 | + >Typeable</a
|
|
| 2052 | + > g</span
|
|
| 2053 | + >, <span class="unbreakable"
|
|
| 2054 | + ><a href="#" title="Data.Dynamic"
|
|
| 2055 | + >Typeable</a
|
|
| 2056 | + > k</span
|
|
| 2057 | + >, <span class="unbreakable"
|
|
| 2058 | + ><a href="#" title="Data.Data"
|
|
| 2059 | + >Data</a
|
|
| 2060 | + > (f a)</span
|
|
| 2061 | + >, <span class="unbreakable"
|
|
| 2062 | + ><a href="#" title="Data.Data"
|
|
| 2063 | + >Data</a
|
|
| 2064 | + > (g a)</span
|
|
| 2065 | + >)</span
|
|
| 2066 | + > => <a href="#" title="Data.Data"
|
|
| 1741 | 2067 | >Data</a
|
| 1742 | 2068 | > (<a href="#" title="Bug1004"
|
| 1743 | 2069 | >Product</a
|
| ... | ... | @@ -1754,7 +2080,7 @@ |
| 1754 | 2080 | ></tr
|
| 1755 | 2081 | ><tr
|
| 1756 | 2082 | ><td colspan="2"
|
| 1757 | - ><details id="i:id:Product:Data:19"
|
|
| 2083 | + ><details id="i:id:Product:Data:23"
|
|
| 1758 | 2084 | ><summary class="hide-when-js-enabled"
|
| 1759 | 2085 | >Instance details</summary
|
| 1760 | 2086 | ><p
|
| ... | ... | @@ -1971,7 +2297,7 @@ |
| 1971 | 2297 | ><tr
|
| 1972 | 2298 | ><td class="src clearfix"
|
| 1973 | 2299 | ><span class="inst-left"
|
| 1974 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Generic:20"
|
|
| 2300 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Generic:24"
|
|
| 1975 | 2301 | ></span
|
| 1976 | 2302 | > <a href="#" title="GHC.Generics"
|
| 1977 | 2303 | >Generic</a
|
| ... | ... | @@ -1986,7 +2312,7 @@ |
| 1986 | 2312 | ></tr
|
| 1987 | 2313 | ><tr
|
| 1988 | 2314 | ><td colspan="2"
|
| 1989 | - ><details id="i:id:Product:Generic:20"
|
|
| 2315 | + ><details id="i:id:Product:Generic:24"
|
|
| 1990 | 2316 | ><summary class="hide-when-js-enabled"
|
| 1991 | 2317 | >Instance details</summary
|
| 1992 | 2318 | ><p
|
| ... | ... | @@ -2125,7 +2451,7 @@ |
| 2125 | 2451 | ><tr
|
| 2126 | 2452 | ><td class="src clearfix"
|
| 2127 | 2453 | ><span class="inst-left"
|
| 2128 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Read:21"
|
|
| 2454 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Read:25"
|
|
| 2129 | 2455 | ></span
|
| 2130 | 2456 | > (<a href="#" title="Prelude"
|
| 2131 | 2457 | >Read</a
|
| ... | ... | @@ -2148,7 +2474,7 @@ |
| 2148 | 2474 | ></tr
|
| 2149 | 2475 | ><tr
|
| 2150 | 2476 | ><td colspan="2"
|
| 2151 | - ><details id="i:id:Product:Read:21"
|
|
| 2477 | + ><details id="i:id:Product:Read:25"
|
|
| 2152 | 2478 | ><summary class="hide-when-js-enabled"
|
| 2153 | 2479 | >Instance details</summary
|
| 2154 | 2480 | ><p
|
| ... | ... | @@ -2207,7 +2533,7 @@ |
| 2207 | 2533 | ><tr
|
| 2208 | 2534 | ><td class="src clearfix"
|
| 2209 | 2535 | ><span class="inst-left"
|
| 2210 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Show:22"
|
|
| 2536 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Show:26"
|
|
| 2211 | 2537 | ></span
|
| 2212 | 2538 | > (<a href="#" title="Prelude"
|
| 2213 | 2539 | >Show</a
|
| ... | ... | @@ -2230,7 +2556,7 @@ |
| 2230 | 2556 | ></tr
|
| 2231 | 2557 | ><tr
|
| 2232 | 2558 | ><td colspan="2"
|
| 2233 | - ><details id="i:id:Product:Show:22"
|
|
| 2559 | + ><details id="i:id:Product:Show:26"
|
|
| 2234 | 2560 | ><summary class="hide-when-js-enabled"
|
| 2235 | 2561 | >Instance details</summary
|
| 2236 | 2562 | ><p
|
| ... | ... | @@ -2279,195 +2605,7 @@ |
| 2279 | 2605 | ><tr
|
| 2280 | 2606 | ><td class="src clearfix"
|
| 2281 | 2607 | ><span class="inst-left"
|
| 2282 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Eq:23"
|
|
| 2283 | - ></span
|
|
| 2284 | - > (<a href="#" title="Data.Eq"
|
|
| 2285 | - >Eq</a
|
|
| 2286 | - > (f a), <a href="#" title="Data.Eq"
|
|
| 2287 | - >Eq</a
|
|
| 2288 | - > (g a)) => <a href="#" title="Data.Eq"
|
|
| 2289 | - >Eq</a
|
|
| 2290 | - > (<a href="#" title="Bug1004"
|
|
| 2291 | - >Product</a
|
|
| 2292 | - > f g a)</span
|
|
| 2293 | - > <a href="#" class="selflink"
|
|
| 2294 | - >#</a
|
|
| 2295 | - ></td
|
|
| 2296 | - ><td class="doc"
|
|
| 2297 | - ><p
|
|
| 2298 | - ><em
|
|
| 2299 | - >Since: base-4.18.0.0</em
|
|
| 2300 | - ></p
|
|
| 2301 | - ></td
|
|
| 2302 | - ></tr
|
|
| 2303 | - ><tr
|
|
| 2304 | - ><td colspan="2"
|
|
| 2305 | - ><details id="i:id:Product:Eq:23"
|
|
| 2306 | - ><summary class="hide-when-js-enabled"
|
|
| 2307 | - >Instance details</summary
|
|
| 2308 | - ><p
|
|
| 2309 | - >Defined in <a href="#"
|
|
| 2310 | - >Data.Functor.Product</a
|
|
| 2311 | - ></p
|
|
| 2312 | - > <div class="subs methods"
|
|
| 2313 | - ><p class="caption"
|
|
| 2314 | - >Methods</p
|
|
| 2315 | - ><p class="src"
|
|
| 2316 | - ><a href="#"
|
|
| 2317 | - >(==)</a
|
|
| 2318 | - > :: <a href="#" title="Bug1004"
|
|
| 2319 | - >Product</a
|
|
| 2320 | - > f g a -> <a href="#" title="Bug1004"
|
|
| 2321 | - >Product</a
|
|
| 2322 | - > f g a -> <a href="#" title="Data.Bool"
|
|
| 2323 | - >Bool</a
|
|
| 2324 | - > <a href="#" class="selflink"
|
|
| 2325 | - >#</a
|
|
| 2326 | - ></p
|
|
| 2327 | - ><p class="src"
|
|
| 2328 | - ><a href="#"
|
|
| 2329 | - >(/=)</a
|
|
| 2330 | - > :: <a href="#" title="Bug1004"
|
|
| 2331 | - >Product</a
|
|
| 2332 | - > f g a -> <a href="#" title="Bug1004"
|
|
| 2333 | - >Product</a
|
|
| 2334 | - > f g a -> <a href="#" title="Data.Bool"
|
|
| 2335 | - >Bool</a
|
|
| 2336 | - > <a href="#" class="selflink"
|
|
| 2337 | - >#</a
|
|
| 2338 | - ></p
|
|
| 2339 | - ></div
|
|
| 2340 | - ></details
|
|
| 2341 | - ></td
|
|
| 2342 | - ></tr
|
|
| 2343 | - ><tr
|
|
| 2344 | - ><td class="src clearfix"
|
|
| 2345 | - ><span class="inst-left"
|
|
| 2346 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Ord:24"
|
|
| 2347 | - ></span
|
|
| 2348 | - > (<a href="#" title="Data.Ord"
|
|
| 2349 | - >Ord</a
|
|
| 2350 | - > (f a), <a href="#" title="Data.Ord"
|
|
| 2351 | - >Ord</a
|
|
| 2352 | - > (g a)) => <a href="#" title="Data.Ord"
|
|
| 2353 | - >Ord</a
|
|
| 2354 | - > (<a href="#" title="Bug1004"
|
|
| 2355 | - >Product</a
|
|
| 2356 | - > f g a)</span
|
|
| 2357 | - > <a href="#" class="selflink"
|
|
| 2358 | - >#</a
|
|
| 2359 | - ></td
|
|
| 2360 | - ><td class="doc"
|
|
| 2361 | - ><p
|
|
| 2362 | - ><em
|
|
| 2363 | - >Since: base-4.18.0.0</em
|
|
| 2364 | - ></p
|
|
| 2365 | - ></td
|
|
| 2366 | - ></tr
|
|
| 2367 | - ><tr
|
|
| 2368 | - ><td colspan="2"
|
|
| 2369 | - ><details id="i:id:Product:Ord:24"
|
|
| 2370 | - ><summary class="hide-when-js-enabled"
|
|
| 2371 | - >Instance details</summary
|
|
| 2372 | - ><p
|
|
| 2373 | - >Defined in <a href="#"
|
|
| 2374 | - >Data.Functor.Product</a
|
|
| 2375 | - ></p
|
|
| 2376 | - > <div class="subs methods"
|
|
| 2377 | - ><p class="caption"
|
|
| 2378 | - >Methods</p
|
|
| 2379 | - ><p class="src"
|
|
| 2380 | - ><a href="#"
|
|
| 2381 | - >compare</a
|
|
| 2382 | - > :: <a href="#" title="Bug1004"
|
|
| 2383 | - >Product</a
|
|
| 2384 | - > f g a -> <a href="#" title="Bug1004"
|
|
| 2385 | - >Product</a
|
|
| 2386 | - > f g a -> <a href="#" title="Data.Ord"
|
|
| 2387 | - >Ordering</a
|
|
| 2388 | - > <a href="#" class="selflink"
|
|
| 2389 | - >#</a
|
|
| 2390 | - ></p
|
|
| 2391 | - ><p class="src"
|
|
| 2392 | - ><a href="#"
|
|
| 2393 | - >(<)</a
|
|
| 2394 | - > :: <a href="#" title="Bug1004"
|
|
| 2395 | - >Product</a
|
|
| 2396 | - > f g a -> <a href="#" title="Bug1004"
|
|
| 2397 | - >Product</a
|
|
| 2398 | - > f g a -> <a href="#" title="Data.Bool"
|
|
| 2399 | - >Bool</a
|
|
| 2400 | - > <a href="#" class="selflink"
|
|
| 2401 | - >#</a
|
|
| 2402 | - ></p
|
|
| 2403 | - ><p class="src"
|
|
| 2404 | - ><a href="#"
|
|
| 2405 | - >(<=)</a
|
|
| 2406 | - > :: <a href="#" title="Bug1004"
|
|
| 2407 | - >Product</a
|
|
| 2408 | - > f g a -> <a href="#" title="Bug1004"
|
|
| 2409 | - >Product</a
|
|
| 2410 | - > f g a -> <a href="#" title="Data.Bool"
|
|
| 2411 | - >Bool</a
|
|
| 2412 | - > <a href="#" class="selflink"
|
|
| 2413 | - >#</a
|
|
| 2414 | - ></p
|
|
| 2415 | - ><p class="src"
|
|
| 2416 | - ><a href="#"
|
|
| 2417 | - >(>)</a
|
|
| 2418 | - > :: <a href="#" title="Bug1004"
|
|
| 2419 | - >Product</a
|
|
| 2420 | - > f g a -> <a href="#" title="Bug1004"
|
|
| 2421 | - >Product</a
|
|
| 2422 | - > f g a -> <a href="#" title="Data.Bool"
|
|
| 2423 | - >Bool</a
|
|
| 2424 | - > <a href="#" class="selflink"
|
|
| 2425 | - >#</a
|
|
| 2426 | - ></p
|
|
| 2427 | - ><p class="src"
|
|
| 2428 | - ><a href="#"
|
|
| 2429 | - >(>=)</a
|
|
| 2430 | - > :: <a href="#" title="Bug1004"
|
|
| 2431 | - >Product</a
|
|
| 2432 | - > f g a -> <a href="#" title="Bug1004"
|
|
| 2433 | - >Product</a
|
|
| 2434 | - > f g a -> <a href="#" title="Data.Bool"
|
|
| 2435 | - >Bool</a
|
|
| 2436 | - > <a href="#" class="selflink"
|
|
| 2437 | - >#</a
|
|
| 2438 | - ></p
|
|
| 2439 | - ><p class="src"
|
|
| 2440 | - ><a href="#"
|
|
| 2441 | - >max</a
|
|
| 2442 | - > :: <a href="#" title="Bug1004"
|
|
| 2443 | - >Product</a
|
|
| 2444 | - > f g a -> <a href="#" title="Bug1004"
|
|
| 2445 | - >Product</a
|
|
| 2446 | - > f g a -> <a href="#" title="Bug1004"
|
|
| 2447 | - >Product</a
|
|
| 2448 | - > f g a <a href="#" class="selflink"
|
|
| 2449 | - >#</a
|
|
| 2450 | - ></p
|
|
| 2451 | - ><p class="src"
|
|
| 2452 | - ><a href="#"
|
|
| 2453 | - >min</a
|
|
| 2454 | - > :: <a href="#" title="Bug1004"
|
|
| 2455 | - >Product</a
|
|
| 2456 | - > f g a -> <a href="#" title="Bug1004"
|
|
| 2457 | - >Product</a
|
|
| 2458 | - > f g a -> <a href="#" title="Bug1004"
|
|
| 2459 | - >Product</a
|
|
| 2460 | - > f g a <a href="#" class="selflink"
|
|
| 2461 | - >#</a
|
|
| 2462 | - ></p
|
|
| 2463 | - ></div
|
|
| 2464 | - ></details
|
|
| 2465 | - ></td
|
|
| 2466 | - ></tr
|
|
| 2467 | - ><tr
|
|
| 2468 | - ><td class="src clearfix"
|
|
| 2469 | - ><span class="inst-left"
|
|
| 2470 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep1:25"
|
|
| 2608 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep1:27"
|
|
| 2471 | 2609 | ></span
|
| 2472 | 2610 | > <span class="keyword"
|
| 2473 | 2611 | >type</span
|
| ... | ... | @@ -2490,7 +2628,7 @@ |
| 2490 | 2628 | ></tr
|
| 2491 | 2629 | ><tr
|
| 2492 | 2630 | ><td colspan="2"
|
| 2493 | - ><details id="i:id:Product:Rep1:25"
|
|
| 2631 | + ><details id="i:id:Product:Rep1:27"
|
|
| 2494 | 2632 | ><summary class="hide-when-js-enabled"
|
| 2495 | 2633 | >Instance details</summary
|
| 2496 | 2634 | ><p
|
| ... | ... | @@ -2565,7 +2703,7 @@ |
| 2565 | 2703 | ><tr
|
| 2566 | 2704 | ><td class="src clearfix"
|
| 2567 | 2705 | ><span class="inst-left"
|
| 2568 | - ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep:26"
|
|
| 2706 | + ><span class="instance details-toggle-control details-toggle" data-details-id="i:id:Product:Rep:28"
|
|
| 2569 | 2707 | ></span
|
| 2570 | 2708 | > <span class="keyword"
|
| 2571 | 2709 | >type</span
|
| ... | ... | @@ -2586,7 +2724,7 @@ |
| 2586 | 2724 | ></tr
|
| 2587 | 2725 | ><tr
|
| 2588 | 2726 | ><td colspan="2"
|
| 2589 | - ><details id="i:id:Product:Rep:26"
|
|
| 2727 | + ><details id="i:id:Product:Rep:28"
|
|
| 2590 | 2728 | ><summary class="hide-when-js-enabled"
|
| 2591 | 2729 | >Instance details</summary
|
| 2592 | 2730 | ><p
|
| ... | ... | @@ -308,8 +308,10 @@ |
| 308 | 308 | ></p
|
| 309 | 309 | ><div class="doc"
|
| 310 | 310 | ><p
|
| 311 | - >Doc for (<code class="inline-code"
|
|
| 312 | - >><</code
|
|
| 311 | + >Doc for (<code
|
|
| 312 | + ><a href="#" title="PatternSyns"
|
|
| 313 | + >><</a
|
|
| 314 | + ></code
|
|
| 313 | 315 | >)</p
|
| 314 | 316 | ></div
|
| 315 | 317 | ><div class="subs constructors"
|
| ... | ... | @@ -48,6 +48,34 @@ |
| 48 | 48 | ><p class="caption"
|
| 49 | 49 | >TypeOperators</p
|
| 50 | 50 | ></div
|
| 51 | + ><div id="description"
|
|
| 52 | + ><p class="caption"
|
|
| 53 | + >Description</p
|
|
| 54 | + ><div class="doc"
|
|
| 55 | + ><p
|
|
| 56 | + >This documentation refers to <code
|
|
| 57 | + ><a href="#" title="Data.Type.Equality"
|
|
| 58 | + >~</a
|
|
| 59 | + ></code
|
|
| 60 | + >, <code
|
|
| 61 | + ><a href="#" title="TypeOperators"
|
|
| 62 | + >:-:</a
|
|
| 63 | + ></code
|
|
| 64 | + >, <code
|
|
| 65 | + ><a href="#" title="TypeOperators"
|
|
| 66 | + >:+:</a
|
|
| 67 | + ></code
|
|
| 68 | + >, <code
|
|
| 69 | + ><a href="#" title="TypeOperators"
|
|
| 70 | + ><=></a
|
|
| 71 | + ></code
|
|
| 72 | + >, and <code
|
|
| 73 | + ><a href="#" title="TypeOperators"
|
|
| 74 | + >|||</a
|
|
| 75 | + ></code
|
|
| 76 | + >.</p
|
|
| 77 | + ></div
|
|
| 78 | + ></div
|
|
| 51 | 79 | ><div id="interface"
|
| 52 | 80 | ><h1
|
| 53 | 81 | >Documentation</h1
|
| ... | ... | @@ -142,6 +170,18 @@ |
| 142 | 170 | ></p
|
| 143 | 171 | ></div
|
| 144 | 172 | ><div class="top"
|
| 173 | + ><p class="src"
|
|
| 174 | + ><span class="keyword"
|
|
| 175 | + >type</span
|
|
| 176 | + > <a id="t:-124--124--124-" class="def"
|
|
| 177 | + >(|||)</a
|
|
| 178 | + > = <a href="#" title="Data.Either"
|
|
| 179 | + >Either</a
|
|
| 180 | + > <a href="#" class="selflink"
|
|
| 181 | + >#</a
|
|
| 182 | + ></p
|
|
| 183 | + ></div
|
|
| 184 | + ><div class="top"
|
|
| 145 | 185 | ><p class="src"
|
| 146 | 186 | ><a id="v:biO" class="def"
|
| 147 | 187 | >biO</a
|
| 1 | 1 | {-# LANGUAGE Haskell2010 #-}
|
| 2 | 2 | {-# LANGUAGE TypeOperators, GADTs, MultiParamTypeClasses, FlexibleContexts #-}
|
| 3 | +-- | This documentation refers to '~', ':-:', ':+:', '<=>', and '|||'.
|
|
| 3 | 4 | module TypeOperators where
|
| 4 | 5 | |
| 5 | 6 | data a :-: b
|
| ... | ... | @@ -12,6 +13,8 @@ newtype (g `O` f) a = O { unO :: g (f a) } |
| 12 | 13 | |
| 13 | 14 | class a <=> b
|
| 14 | 15 | |
| 16 | +type (|||) = Either
|
|
| 17 | + |
|
| 15 | 18 | biO :: (g `O` f) a
|
| 16 | 19 | biO = undefined
|
| 17 | 20 |