[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Typeset Big-O complexities with Tex-style notation (#16090)

Marge Bot gitlab at gitlab.haskell.org
Thu Apr 18 04:01:51 UTC 2019



 Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
e142ec99 by Sven Tennie at 2019-04-18T03:19:00Z
Typeset Big-O complexities with Tex-style notation (#16090)

E.g. use `\(\mathcal{O}(n^2)\)` instead of `/O(n^2)/`.

- - - - -
f0f495f0 by klebinger.andreas at gmx.at at 2019-04-18T03:25:10Z
Add an Outputable instance for SDoc with ppr = id.

When printf debugging this can be helpful.

- - - - -
6595ef0d by Sylvain Henry at 2019-04-18T04:01:43Z
Gitlab: allow execution of CI pipeline from the web interface
[skip ci]

- - - - -
3d367bfa by Alp Mestanogullari at 2019-04-18T04:01:45Z
Hadrian: fix ghcDebugged and document it

- - - - -


13 changed files:

- .gitlab-ci.yml
- compiler/utils/Outputable.hs
- hadrian/doc/user-settings.md
- hadrian/src/Expression.hs
- hadrian/src/Packages.hs
- hadrian/src/Settings/Builders/Ghc.hs
- libraries/base/Data/Foldable.hs
- libraries/base/Data/OldList.hs
- libraries/base/Data/Semigroup/Internal.hs
- libraries/base/GHC/Base.hs
- libraries/base/GHC/List.hs
- libraries/base/GHC/StableName.hs
- libraries/base/System/Mem/StableName.hs


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -30,6 +30,7 @@ stages:
     - /ghc-[0-9]+\.[0-9]+/
     - merge_requests
     - tags
+    - web
 
 ############################################################
 # Runner Tags


=====================================
compiler/utils/Outputable.hs
=====================================
@@ -327,6 +327,10 @@ data SDocContext = SDC
 instance IsString SDoc where
   fromString = text
 
+-- The lazy programmer's friend.
+instance Outputable SDoc where
+  ppr = id
+
 initSDocContext :: DynFlags -> PprStyle -> SDocContext
 initSDocContext dflags sty = SDC
   { sdocStyle = sty


=====================================
hadrian/doc/user-settings.md
=====================================
@@ -114,6 +114,21 @@ devel2WerrorFlavour :: Flavour
 devel2WerrorFlavour = werror (developmentFlavour Stage2)
 ```
 
+### Linking GHC against the debugged RTS
+
+What was previously achieved by having `GhcDebugged=YES` in `mk/build.mk` can
+be done by defining a custom flavour in the user settings file, one that
+sets the `ghcDebugged` field of `Flavour` to `True`, e.g:
+
+``` haskell
+quickDebug :: Flavour
+quickDebug = quickFlavour { name = "dbg", ghcDebugged = True }
+```
+
+Running `build --flavour=dbg` will build a `quick`-flavoured GHC and link
+GHC, iserv, iserv-proxy and remote-iserv against the debugged RTS, by passing
+`-debug` to the commands that link those executables.
+
 ## Packages
 
 Users can add and remove packages from particular build stages. As an example,


=====================================
hadrian/src/Expression.hs
=====================================
@@ -7,7 +7,7 @@ module Expression (
 
     -- ** Predicates
     (?), stage, stage0, stage1, stage2, notStage0, package, notPackage,
-    libraryPackage, builder, way, input, inputs, output, outputs,
+     packageOneOf, libraryPackage, builder, way, input, inputs, output, outputs,
 
     -- ** Evaluation
     interpret, interpretInContext,
@@ -44,6 +44,9 @@ stage s = (s ==) <$> getStage
 package :: Package -> Predicate
 package p = (p ==) <$> getPackage
 
+packageOneOf :: [Package] -> Predicate
+packageOneOf ps = (`elem` ps) <$> getPackage
+
 -- | This type class allows the user to construct both precise builder
 -- predicates, such as @builder (Ghc CompileHs Stage1)@, as well as predicates
 -- covering a set of similar builders. For example, @builder (Ghc CompileHs)@


=====================================
hadrian/src/Packages.hs
=====================================
@@ -5,10 +5,10 @@ module Packages (
     compareSizes, compiler, containers, deepseq, deriveConstants, directory,
     filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCompact,
     ghcHeap, ghci, ghcPkg, ghcPrim, haddock, haskeline,
-    hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, libffi,
-    libiserv, mtl, parsec, pretty, primitive, process, rts, runGhc,
-    stm, templateHaskell, terminfo, text, time, timeout, touchy, transformers,
-    unlit, unix, win32, xhtml, ghcPackages, isGhcPackage,
+    hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, iservProxy,
+    libffi, libiserv, mtl, parsec, pretty, primitive, process, remoteIserv, rts,
+    runGhc, stm, templateHaskell, terminfo, text, time, timeout, touchy,
+    transformers, unlit, unix, win32, xhtml, ghcPackages, isGhcPackage,
 
     -- * Package information
     programName, nonHsMainPackage, autogenPath, programPath, timeoutPath,
@@ -78,6 +78,7 @@ hpcBin              = util "hpc-bin"         `setPath` "utils/hpc"
 integerGmp          = lib  "integer-gmp"
 integerSimple       = lib  "integer-simple"
 iserv               = util "iserv"
+iservProxy          = util "iserv-proxy"
 libffi              = top  "libffi"
 libiserv            = lib  "libiserv"
 mtl                 = lib  "mtl"
@@ -85,6 +86,7 @@ parsec              = lib  "parsec"
 pretty              = lib  "pretty"
 primitive           = lib  "primitive"
 process             = lib  "process"
+remoteIserv         = util "remote-iserv"
 rts                 = top  "rts"
 runGhc              = util "runghc"
 stm                 = lib  "stm"


=====================================
hadrian/src/Settings/Builders/Ghc.hs
=====================================
@@ -3,6 +3,7 @@ module Settings.Builders.Ghc (ghcBuilderArgs, haddockGhcArgs) where
 import Hadrian.Haskell.Cabal
 import Hadrian.Haskell.Cabal.Type
 
+import Flavour
 import Packages
 import Settings.Builders.Common
 import Settings.Warnings
@@ -69,6 +70,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
     useSystemFfi <- expr (flag UseSystemFfi)
     buildPath <- getBuildPath
     libffiName' <- libffiName
+    debugged <- ghcDebugged <$> expr flavour
 
     let
         dynamic = Dynamic `wayUnit` way
@@ -110,6 +112,9 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
             , pure [ "-L" ++ libDir | libDir <- libDirs ]
             , rtsFfiArg
             , darwin ? pure (concat [ ["-framework", fmwk] | fmwk <- fmwks ])
+            , debugged ? packageOneOf [ghc, iservProxy, iserv, remoteIserv] ?
+              arg "-debug"
+
             ]
 
 findHsDependencies :: Args


=====================================
libraries/base/Data/Foldable.hs
=====================================
@@ -181,8 +181,8 @@ class Foldable t where
     -- use 'foldl'' instead of 'foldl'. The reason for this is that latter does
     -- not force the "inner" results (e.g. @z \`f\` x1@ in the above example)
     -- before applying them to the operator (e.g. to @(\`f\` x2)@). This results
-    -- in a thunk chain @O(n)@ elements long, which then must be evaluated from
-    -- the outside-in.
+    -- in a thunk chain \(\mathcal{O}(n)\) elements long, which then must be
+    -- evaluated from the outside-in.
     --
     -- For a general 'Foldable' structure this should be semantically identical
     -- to,


=====================================
libraries/base/Data/OldList.hs
=====================================
@@ -241,9 +241,9 @@ infix 5 \\ -- comment to fool cpp: https://downloads.haskell.org/~ghc/latest/doc
 dropWhileEnd :: (a -> Bool) -> [a] -> [a]
 dropWhileEnd p = foldr (\x xs -> if p x && null xs then [] else x : xs) []
 
--- | /O(min(m,n))/. The 'stripPrefix' function drops the given prefix from a
--- list. It returns 'Nothing' if the list did not start with the prefix given,
--- or 'Just' the list after the prefix, if it does.
+-- | \(\mathcal{O}(min(m,n))\). The 'stripPrefix' function drops the given
+-- prefix from a list. It returns 'Nothing' if the list did not start with the
+-- prefix given, or 'Just' the list after the prefix, if it does.
 --
 -- >>> stripPrefix "foo" "foobar"
 -- Just "bar"
@@ -319,8 +319,8 @@ findIndices p ls = build $ \c n ->
   in foldr go (\_ -> n) ls 0#
 #endif  /* USE_REPORT_PRELUDE */
 
--- | /O(min(m,n))/. The 'isPrefixOf' function takes two lists and returns 'True'
--- iff the first list is a prefix of the second.
+-- | \(\mathcal{O}(min(m,n))\). The 'isPrefixOf' function takes two lists and
+-- returns 'True' iff the first list is a prefix of the second.
 --
 -- >>> "Hello" `isPrefixOf` "Hello World!"
 -- True
@@ -388,11 +388,10 @@ dropLengthMaybe (_:x') (_:y') = dropLengthMaybe x' y'
 isInfixOf               :: (Eq a) => [a] -> [a] -> Bool
 isInfixOf needle haystack = any (isPrefixOf needle) (tails haystack)
 
--- | /O(n^2)/. The 'nub' function removes duplicate elements from a list.
--- In particular, it keeps only the first occurrence of each element.
--- (The name 'nub' means \`essence\'.)
--- It is a special case of 'nubBy', which allows the programmer to supply
--- their own equality test.
+-- | \(\mathcal{O}(n^2)\). The 'nub' function removes duplicate elements from a
+-- list. In particular, it keeps only the first occurrence of each element. (The
+-- name 'nub' means \`essence\'.) It is a special case of 'nubBy', which allows
+-- the programmer to supply their own equality test.
 --
 -- >>> nub [1,2,3,4,3,2,1,2,4,3,5]
 -- [1,2,3,4,5]
@@ -431,8 +430,8 @@ elem_by eq y (x:xs)     =  x `eq` y || elem_by eq y xs
 #endif
 
 
--- | /O(n)/. 'delete' @x@ removes the first occurrence of @x@ from its list
--- argument. For example,
+-- | \(\mathcal{O}(n)\). 'delete' @x@ removes the first occurrence of @x@ from
+-- its list argument. For example,
 --
 -- >>> delete 'a' "banana"
 -- "bnana"
@@ -442,8 +441,8 @@ elem_by eq y (x:xs)     =  x `eq` y || elem_by eq y xs
 delete                  :: (Eq a) => a -> [a] -> [a]
 delete                  =  deleteBy (==)
 
--- | /O(n)/. The 'deleteBy' function behaves like 'delete', but takes a
--- user-supplied equality predicate.
+-- | \(\mathcal{O}(n)\). The 'deleteBy' function behaves like 'delete', but
+-- takes a user-supplied equality predicate.
 --
 -- >>> deleteBy (<=) 4 [1..10]
 -- [1,2,3,5,6,7,8,9,10]
@@ -509,9 +508,9 @@ intersectBy _  [] _     =  []
 intersectBy _  _  []    =  []
 intersectBy eq xs ys    =  [x | x <- xs, any (eq x) ys]
 
--- | /O(n)/. The 'intersperse' function takes an element and a list and
--- \`intersperses\' that element between the elements of the list.
--- For example,
+-- | \(\mathcal{O}(n)\). The 'intersperse' function takes an element and a list
+-- and \`intersperses\' that element between the elements of the list. For
+-- example,
 --
 -- >>> intersperse ',' "abcde"
 -- "a,b,c,d,e"
@@ -618,18 +617,18 @@ mapAccumR f s (x:xs)    =  (s'', y:ys)
                            where (s'',y ) = f s' x
                                  (s', ys) = mapAccumR f s xs
 
--- | /O(n)/. The 'insert' function takes an element and a list and inserts the
--- element into the list at the first position where it is less than or equal to
--- the next element. In particular, if the list is sorted before the call, the
--- result will also be sorted. It is a special case of 'insertBy', which allows
--- the programmer to supply their own comparison function.
+-- | \(\mathcal{O}(n)\). The 'insert' function takes an element and a list and
+-- inserts the element into the list at the first position where it is less than
+-- or equal to the next element. In particular, if the list is sorted before the
+-- call, the result will also be sorted. It is a special case of 'insertBy',
+-- which allows the programmer to supply their own comparison function.
 --
 -- >>> insert 4 [1,2,3,5,6,7]
 -- [1,2,3,4,5,6,7]
 insert :: Ord a => a -> [a] -> [a]
 insert e ls = insertBy (compare) e ls
 
--- | /O(n)/. The non-overloaded version of 'insert'.
+-- | \(\mathcal{O}(n)\). The non-overloaded version of 'insert'.
 insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]
 insertBy _   x [] = [x]
 insertBy cmp x ys@(y:ys')
@@ -669,9 +668,10 @@ minimumBy cmp xs        =  foldl1 minBy xs
                                        GT -> y
                                        _  -> x
 
--- | /O(n)/. The 'genericLength' function is an overloaded version of 'length'.
--- In particular, instead of returning an 'Int', it returns any type which is an
--- instance of 'Num'. It is, however, less efficient than 'length'.
+-- | \(\mathcal{O}(n)\). The 'genericLength' function is an overloaded version
+-- of 'length'. In particular, instead of returning an 'Int', it returns any
+-- type which is an instance of 'Num'. It is, however, less efficient than
+-- 'length'.
 --
 -- >>> genericLength [1, 2, 3] :: Int
 -- 3
@@ -1029,8 +1029,8 @@ inits                   = map toListSB . scanl' snocSB emptySB
 -- if it fuses with a consumer, and it would generally lead to serious
 -- loss of sharing if allowed to fuse with a producer.
 
--- | /O(n)/. The 'tails' function returns all final segments of the argument,
--- longest first.  For example,
+-- | \(\mathcal{O}(n)\). The 'tails' function returns all final segments of the
+-- argument, longest first. For example,
 --
 -- >>> tails "abc"
 -- ["abc","bc","c",""]


=====================================
libraries/base/Data/Semigroup/Internal.hs
=====================================
@@ -31,7 +31,7 @@ import GHC.Real
 -- | This is a valid definition of 'stimes' for an idempotent 'Semigroup'.
 --
 -- When @x <> x = x@, this definition should be preferred, because it
--- works in /O(1)/ rather than /O(log n)/.
+-- works in \(\mathcal{O}(1)\) rather than \(\mathcal{O}(\log n)\).
 stimesIdempotent :: Integral b => b -> a -> a
 stimesIdempotent n x
   | n <= 0 = errorWithoutStackTrace "stimesIdempotent: positive multiplier expected"
@@ -40,7 +40,7 @@ stimesIdempotent n x
 -- | This is a valid definition of 'stimes' for an idempotent 'Monoid'.
 --
 -- When @mappend x x = x@, this definition should be preferred, because it
--- works in /O(1)/ rather than /O(log n)/
+-- works in \(\mathcal{O}(1)\) rather than \(\mathcal{O}(\log n)\)
 stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a
 stimesIdempotentMonoid n x = case compare n 0 of
   LT -> errorWithoutStackTrace "stimesIdempotentMonoid: negative multiplier"


=====================================
libraries/base/GHC/Base.hs
=====================================
@@ -239,7 +239,7 @@ class Semigroup a where
         -- will do so.
         --
         -- By making this a member of the class, idempotent semigroups
-        -- and monoids can upgrade this to execute in /O(1)/ by
+        -- and monoids can upgrade this to execute in \(\mathcal{O}(1)\) by
         -- picking @stimes = 'Data.Semigroup.stimesIdempotent'@ or @stimes =
         -- 'stimesIdempotentMonoid'@ respectively.
         stimes :: Integral b => b -> a -> a
@@ -1083,8 +1083,8 @@ augment g xs = g (:) xs
 --              map
 ----------------------------------------------
 
--- | /O(n)/. 'map' @f xs@ is the list obtained by applying @f@ to each element
--- of @xs@, i.e.,
+-- | \(\mathcal{O}(n)\). 'map' @f xs@ is the list obtained by applying @f@ to
+-- each element of @xs@, i.e.,
 --
 -- > map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn]
 -- > map f [x1, x2, ...] == [f x1, f x2, ...]


=====================================
libraries/base/GHC/List.hs
=====================================
@@ -44,7 +44,7 @@ infix  4 `elem`, `notElem`
 -- List-manipulation functions
 --------------------------------------------------------------
 
--- | /O(1)/. Extract the first element of a list, which must be non-empty.
+-- | \(\mathcal{O}(1)\). Extract the first element of a list, which must be non-empty.
 head                    :: [a] -> a
 head (x:_)              =  x
 head []                 =  badHead
@@ -62,8 +62,8 @@ badHead = errorEmptyList "head"
                 head (augment g xs) = g (\x _ -> x) (head xs)
  #-}
 
--- | /O(1)/. Decompose a list into its head and tail. If the list is empty,
--- returns 'Nothing'. If the list is non-empty, returns @'Just' (x, xs)@,
+-- | \(\mathcal{O}(1)\). Decompose a list into its head and tail. If the list is
+-- empty, returns 'Nothing'. If the list is non-empty, returns @'Just' (x, xs)@,
 -- where @x@ is the head of the list and @xs@ its tail.
 --
 -- @since 4.8.0.0
@@ -71,14 +71,14 @@ uncons                  :: [a] -> Maybe (a, [a])
 uncons []               = Nothing
 uncons (x:xs)           = Just (x, xs)
 
--- | /O(1)/. Extract the elements after the head of a list, which must be
--- non-empty.
+-- | \(\mathcal{O}(1)\). Extract the elements after the head of a list, which
+-- must be non-empty.
 tail                    :: [a] -> [a]
 tail (_:xs)             =  xs
 tail []                 =  errorEmptyList "tail"
 
--- | /O(n)/. Extract the last element of a list, which must be finite and
--- non-empty.
+-- | \(\mathcal{O}(n)\). Extract the last element of a list, which must be
+-- finite and non-empty.
 last                    :: [a] -> a
 #if defined(USE_REPORT_PRELUDE)
 last [x]                =  x
@@ -96,7 +96,7 @@ lastError :: a
 lastError = errorEmptyList "last"
 #endif
 
--- | /O(n)/. Return all the elements of a list except the last one.
+-- | \(\mathcal{O}(n)\). Return all the elements of a list except the last one.
 -- The list must be non-empty.
 init                    :: [a] -> [a]
 #if defined(USE_REPORT_PRELUDE)
@@ -111,14 +111,14 @@ init (x:xs)             =  init' x xs
         init' y (z:zs) = y : init' z zs
 #endif
 
--- | /O(1)/. Test whether a list is empty.
+-- | \(\mathcal{O}(1)\). Test whether a list is empty.
 null                    :: [a] -> Bool
 null []                 =  True
 null (_:_)              =  False
 
--- | /O(n)/. 'length' returns the length of a finite list as an 'Int'.
--- It is an instance of the more general 'Data.List.genericLength',
--- the result type of which may be any kind of number.
+-- | \(\mathcal{O}(n)\). 'length' returns the length of a finite list as an
+-- 'Int'. It is an instance of the more general 'Data.List.genericLength', the
+-- result type of which may be any kind of number.
 {-# NOINLINE [1] length #-}
 length                  :: [a] -> Int
 length xs               = lenAcc xs 0
@@ -142,8 +142,8 @@ lengthFB _ r = \ !a -> r (a + 1)
 idLength :: Int -> Int
 idLength = id
 
--- | /O(n)/. 'filter', applied to a predicate and a list, returns the list of
--- those elements that satisfy the predicate; i.e.,
+-- | \(\mathcal{O}(n)\). 'filter', applied to a predicate and a list, returns
+-- the list of those elements that satisfy the predicate; i.e.,
 --
 -- > filter p xs = [ x | x <- xs, p x]
 --
@@ -262,8 +262,8 @@ product                 :: (Num a) => [a] -> a
 {-# INLINE product #-}
 product                 =  foldl (*) 1
 
--- | /O(n)/. 'scanl' is similar to 'foldl', but returns a list of successive
--- reduced values from the left:
+-- | \(\mathcal{O}(n)\). 'scanl' is similar to 'foldl', but returns a list of
+-- successive reduced values from the left:
 --
 -- > scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
 --
@@ -300,8 +300,8 @@ constScanl :: a -> b -> a
 constScanl = const
 
 
--- | /O(n)/. 'scanl1' is a variant of 'scanl' that has no starting value
--- argument:
+-- | \(\mathcal{O}(n)\). 'scanl1' is a variant of 'scanl' that has no starting
+-- value argument:
 --
 -- > scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
 
@@ -309,7 +309,7 @@ scanl1                  :: (a -> a -> a) -> [a] -> [a]
 scanl1 f (x:xs)         =  scanl f x xs
 scanl1 _ []             =  []
 
--- | /O(n)/. A strictly accumulating version of 'scanl'
+-- | \(\mathcal{O}(n)\). A strictly accumulating version of 'scanl'
 {-# NOINLINE [1] scanl' #-}
 scanl'           :: (b -> a -> b) -> b -> [a] -> [b]
 -- This peculiar form is needed to prevent scanl' from being rewritten
@@ -381,7 +381,7 @@ foldr1 f = go
         go []             =  errorEmptyList "foldr1"
 {-# INLINE [0] foldr1 #-}
 
--- | /O(n)/. 'scanr' is the right-to-left dual of 'scanl'.
+-- | \(\mathcal{O}(n)\). 'scanr' is the right-to-left dual of 'scanl'.
 -- Note that
 --
 -- > head (scanr f z xs) == foldr f z xs.
@@ -408,8 +408,8 @@ scanrFB f c = \x (r, est) -> (f x r, r `c` est)
                  scanr f q0 ls
  #-}
 
--- | /O(n)/. 'scanr1' is a variant of 'scanr' that has no starting value
--- argument.
+-- | \(\mathcal{O}(n)\). 'scanr1' is a variant of 'scanr' that has no starting
+-- value argument.
 scanr1                  :: (a -> a -> a) -> [a] -> [a]
 scanr1 _ []             =  []
 scanr1 _ [x]            =  [x]
@@ -852,7 +852,8 @@ notElem x (y:ys)=  x /= y && notElem x ys
  #-}
 #endif
 
--- | /O(n)/. 'lookup' @key assocs@ looks up a key in an association list.
+-- | \(\mathcal{O}(n)\). 'lookup' @key assocs@ looks up a key in an association
+-- list.
 --
 -- >>> lookup 2 [(1, "first"), (2, "second"), (3, "third")]
 -- Just "second"
@@ -1012,8 +1013,8 @@ NB: Zips for larger tuples are in the List module.
 -}
 
 ----------------------------------------------
--- | /O(min(m,n))/. 'zip' takes two lists and returns a list of corresponding
--- pairs.
+-- | \(\mathcal{O}(min(m,n))\). 'zip' takes two lists and returns a list of
+-- corresponding pairs.
 --
 -- > zip [1, 2] ['a', 'b'] = [(1, 'a'), (2, 'b')]
 --
@@ -1070,10 +1071,10 @@ zip3FB cons = \a b c r -> (a,b,c) `cons` r
 -- function given as the first argument, instead of a tupling function.
 
 ----------------------------------------------
--- | /O(min(m,n))/. 'zipWith' generalises 'zip' by zipping with the function
--- given as the first argument, instead of a tupling function. For example,
--- @'zipWith' (+)@ is applied to two lists to produce the list of corresponding
--- sums:
+-- | \(\mathcal{O}(min(m,n))\). 'zipWith' generalises 'zip' by zipping with the
+-- function given as the first argument, instead of a tupling function. For
+-- example, @'zipWith' (+)@ is applied to two lists to produce the list of
+-- corresponding sums:
 --
 -- >>> zipWith (+) [1, 2, 3] [4, 5, 6]
 -- [5,7,9]


=====================================
libraries/base/GHC/StableName.hs
=====================================
@@ -13,8 +13,8 @@
 -- Stability   :  experimental
 -- Portability :  non-portable
 --
--- Stable names are a way of performing fast (O(1)), not-quite-exact
--- comparison between objects.
+-- Stable names are a way of performing fast ( \(\mathcal{O}(1)\) ),
+-- not-quite-exact comparison between objects.
 --
 -- Stable names solve the following problem: suppose you want to build
 -- a hash table with Haskell objects as keys, but you want to use


=====================================
libraries/base/System/Mem/StableName.hs
=====================================
@@ -10,8 +10,8 @@
 -- Stability   :  experimental
 -- Portability :  non-portable
 --
--- Stable names are a way of performing fast (O(1)), not-quite-exact
--- comparison between objects.
+-- Stable names are a way of performing fast ( \(\mathcal{O}(1)\) ),
+-- not-quite-exact comparison between objects.
 --
 -- Stable names solve the following problem: suppose you want to build
 -- a hash table with Haskell objects as keys, but you want to use



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/97a41cd9813dc98efb44d27684a6d98cf5f5168f...3d367bfa98b0ddf9e4a9fcab86def168f73ca503

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/97a41cd9813dc98efb44d27684a6d98cf5f5168f...3d367bfa98b0ddf9e4a9fcab86def168f73ca503
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190418/89f57b60/attachment-0001.html>


More information about the ghc-commits mailing list