diff --git a/ghc/lib/std/PrelBase.lhs b/ghc/lib/std/PrelBase.lhs index 092d4dfd25d6808436b8f2fae93597285f6eaf08..6ef504423ddd49aa547695242e71ece212e81109 100644 --- a/ghc/lib/std/PrelBase.lhs +++ b/ghc/lib/std/PrelBase.lhs @@ -234,7 +234,7 @@ ord = (fromEnum :: Char -> Int) ord_0 :: Num a => a ord_0 = fromInt (ord '0') -{-# GENERATE_SPECS subtract a{Int} #-} +{-# SPECIALISE subtract :: Int -> Int -> Int #-} subtract :: (Num a) => a -> a -> a subtract x y = y - x \end{code} @@ -689,7 +689,6 @@ const x _ = x -- function composition {-# INLINE (.) #-} -{- GENERATE_SPECS (.) a b c -} (.) :: (b -> c) -> (a -> b) -> a -> c (.) f g x = f (g x) @@ -724,7 +723,6 @@ asTypeOf = const \begin{code} data Lift a = Lift a -{- GENERATE_SPECS data a :: Lift a -} \end{code} @@ -752,7 +750,6 @@ showString = (++) showParen :: Bool -> ShowS -> ShowS showParen b p = if b then showChar '(' . p . showChar ')' else p -{- GENERATE_SPECS showList__ a -} showList__ :: (a -> ShowS) -> [a] -> ShowS showList__ showx [] = showString "[]"