diff options
-rw-r--r-- | libraries/base/GHC/Base.lhs | 48 |
1 files changed, 24 insertions, 24 deletions
diff --git a/libraries/base/GHC/Base.lhs b/libraries/base/GHC/Base.lhs index 7f4317a303..303d7162ea 100644 --- a/libraries/base/GHC/Base.lhs +++ b/libraries/base/GHC/Base.lhs @@ -82,13 +82,13 @@ Other Prelude modules are much easier with fewer complex dependencies. -- Module : GHC.Base -- Copyright : (c) The University of Glasgow, 1992-2002 -- License : see libraries/base/LICENSE --- +-- -- Maintainer : cvs-ghc@haskell.org -- Stability : internal -- Portability : non-portable (GHC extensions) -- -- Basic data types and classes. --- +-- ----------------------------------------------------------------------------- #include "MachDeps.h" @@ -103,7 +103,7 @@ module GHC.Base module GHC.Types, module GHC.Prim, -- Re-export GHC.Prim and GHC.Err, to avoid lots module GHC.Err -- of people having to import it explicitly - ) + ) where import GHC.Types @@ -143,7 +143,7 @@ default () -- Double isn't available yet \begin{code} {- data Bool = False | True -data Ordering = LT | EQ | GT +data Ordering = LT | EQ | GT data Char = C# Char# type String = [Char] data Int = I# Int# @@ -266,7 +266,7 @@ The rest of the prelude list functions are in GHC.List. ---------------------------------------------- -- foldr/build/augment ---------------------------------------------- - + \begin{code} -- | 'foldr', applied to a binary operator, a starting value (typically -- the right-identity of the operator), and a list, reduces the list @@ -279,7 +279,7 @@ foldr :: (a -> b -> b) -> b -> [a] -> b -- foldr f z (x:xs) = f x (foldr f z xs) {-# INLINE [0] foldr #-} -- Inline only in the final stage, after the foldr/cons rule has had a chance --- Also note that we inline it when it has *two* parameters, which are the +-- Also note that we inline it when it has *two* parameters, which are the -- ones we are keen about specialising! foldr k z = go where @@ -320,10 +320,10 @@ augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a] augment g xs = g (:) xs {-# RULES -"fold/build" forall k z (g::forall b. (a->b->b) -> b -> b) . +"fold/build" forall k z (g::forall b. (a->b->b) -> b -> b) . foldr k z (build g) = g k z -"foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . +"foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . foldr k z (augment g xs) = g k (foldr k z xs) "foldr/id" foldr (:) [] = \x -> x @@ -340,7 +340,7 @@ augment g xs = g (:) xs -- "foldr/cons" forall k z x xs. foldr k z (x:xs) = k x (foldr k z xs) "foldr/single" forall k z x. foldr k z [x] = k x z -"foldr/nil" forall k z. foldr k z [] = z +"foldr/nil" forall k z. foldr k z [] = z "augment/build" forall (g::forall b. (a->b->b) -> b -> b) (h::forall b. (a->b->b) -> b -> b) . @@ -355,7 +355,7 @@ augment g xs = g (:) xs ---------------------------------------------- --- map +-- map ---------------------------------------------- \begin{code} @@ -366,8 +366,8 @@ augment g xs = g (:) xs -- > map f [x1, x2, ...] == [f x1, f x2, ...] map :: (a -> b) -> [a] -> [b] -{-# NOINLINE [1] map #-} -- We want the RULE to fire first. - -- It's recursive, so won't inline anyway, +{-# NOINLINE [1] map #-} -- We want the RULE to fire first. + -- It's recursive, so won't inline anyway, -- but saying so is more explicit map _ [] = [] map f (x:xs) = f x : map f xs @@ -378,33 +378,33 @@ mapFB :: (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst mapFB c f = \x ys -> c (f x) ys -- The rules for map work like this. --- +-- -- Up to (but not including) phase 1, we use the "map" rule to --- rewrite all saturated applications of map with its build/fold +-- rewrite all saturated applications of map with its build/fold -- form, hoping for fusion to happen. -- In phase 1 and 0, we switch off that rule, inline build, and -- switch on the "mapList" rule, which rewrites the foldr/mapFB --- thing back into plain map. +-- thing back into plain map. -- --- It's important that these two rules aren't both active at once --- (along with build's unfolding) else we'd get an infinite loop +-- It's important that these two rules aren't both active at once +-- (along with build's unfolding) else we'd get an infinite loop -- in the rules. Hence the activation control below. -- -- The "mapFB" rule optimises compositions of map. -- --- This same pattern is followed by many other functions: +-- This same pattern is followed by many other functions: -- e.g. append, filter, iterate, repeat, etc. {-# RULES "map" [~1] forall f xs. map f xs = build (\c n -> foldr (mapFB c f) n xs) "mapList" [1] forall f. foldr (mapFB (:) f) [] = map f -"mapFB" forall c f g. mapFB (mapFB c f) g = mapFB c (f.g) +"mapFB" forall c f g. mapFB (mapFB c f) g = mapFB c (f.g) #-} \end{code} ---------------------------------------------- --- append +-- append ---------------------------------------------- \begin{code} -- | Append two lists, i.e., @@ -415,8 +415,8 @@ mapFB c f = \x ys -> c (f x) ys -- If the first list is not finite, the result is the first list. (++) :: [a] -> [a] -> [a] -{-# NOINLINE [1] (++) #-} -- We want the RULE to fire first. - -- It's recursive, so won't inline anyway, +{-# NOINLINE [1] (++) #-} -- We want the RULE to fire first. + -- It's recursive, so won't inline anyway, -- but saying so is more explicit (++) [] ys = ys (++) (x:xs) ys = x : xs ++ ys @@ -494,7 +494,7 @@ maxInt = I# 0x3FFFFFFF# #elif WORD_SIZE_IN_BITS == 32 minInt = I# (-0x80000000#) maxInt = I# 0x7FFFFFFF# -#else +#else minInt = I# (-0x8000000000000000#) maxInt = I# 0x7FFFFFFFFFFFFFFF# #endif @@ -521,7 +521,7 @@ id x = x -- call to 'assert'. -- -- Assertions can normally be turned on or off with a compiler flag --- (for GHC, assertions are normally on unless optimisation is turned on +-- (for GHC, assertions are normally on unless optimisation is turned on -- with @-O@ or the @-fignore-asserts@ -- option is given). When assertions are turned off, the first -- argument to 'assert' is ignored, and the second argument is |