Skip to content
Snippets Groups Projects
Commit cdf3461f authored by Simon Marlow's avatar Simon Marlow
Browse files

[project @ 1998-05-12 12:45:00 by simonm]

add a specialise pragma and remove some GENERATE_SPECS
parent 7862e46a
No related merge requests found
...@@ -234,7 +234,7 @@ ord = (fromEnum :: Char -> Int) ...@@ -234,7 +234,7 @@ ord = (fromEnum :: Char -> Int)
ord_0 :: Num a => a ord_0 :: Num a => a
ord_0 = fromInt (ord '0') ord_0 = fromInt (ord '0')
{-# GENERATE_SPECS subtract a{Int} #-} {-# SPECIALISE subtract :: Int -> Int -> Int #-}
subtract :: (Num a) => a -> a -> a subtract :: (Num a) => a -> a -> a
subtract x y = y - x subtract x y = y - x
\end{code} \end{code}
...@@ -689,7 +689,6 @@ const x _ = x ...@@ -689,7 +689,6 @@ const x _ = x
-- function composition -- function composition
{-# INLINE (.) #-} {-# INLINE (.) #-}
{- GENERATE_SPECS (.) a b c -}
(.) :: (b -> c) -> (a -> b) -> a -> c (.) :: (b -> c) -> (a -> b) -> a -> c
(.) f g x = f (g x) (.) f g x = f (g x)
...@@ -724,7 +723,6 @@ asTypeOf = const ...@@ -724,7 +723,6 @@ asTypeOf = const
\begin{code} \begin{code}
data Lift a = Lift a data Lift a = Lift a
{- GENERATE_SPECS data a :: Lift a -}
\end{code} \end{code}
...@@ -752,7 +750,6 @@ showString = (++) ...@@ -752,7 +750,6 @@ showString = (++)
showParen :: Bool -> ShowS -> ShowS showParen :: Bool -> ShowS -> ShowS
showParen b p = if b then showChar '(' . p . showChar ')' else p showParen b p = if b then showChar '(' . p . showChar ')' else p
{- GENERATE_SPECS showList__ a -}
showList__ :: (a -> ShowS) -> [a] -> ShowS showList__ :: (a -> ShowS) -> [a] -> ShowS
showList__ showx [] = showString "[]" showList__ showx [] = showString "[]"
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment