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

[project @ 1999-07-14 08:37:57 by simonmar]

USE_REPORT_PRELUDE patches from Wolfram Kahl.
parent d1ab5c38
No related branches found
No related tags found
No related merge requests found
...@@ -22,10 +22,16 @@ module PrelList ( ...@@ -22,10 +22,16 @@ module PrelList (
maximum, minimum, concatMap, maximum, minimum, concatMap,
zip, zip3, zipWith, zipWith3, unzip, unzip3, zip, zip3, zipWith, zipWith3, unzip, unzip3,
#ifdef USE_REPORT_PRELUDE
#else
-- non-standard, but hidden when creating the Prelude -- non-standard, but hidden when creating the Prelude
-- export list. -- export list.
takeUInt_append takeUInt_append
#endif
) where ) where
import {-# SOURCE #-} PrelErr ( error ) import {-# SOURCE #-} PrelErr ( error )
...@@ -241,20 +247,20 @@ dropWhile p xs@(x:xs') ...@@ -241,20 +247,20 @@ dropWhile p xs@(x:xs')
take :: Int -> [a] -> [a] take :: Int -> [a] -> [a]
take 0 _ = [] take 0 _ = []
take _ [] = [] take _ [] = []
take n (x:xs) | n > 0 = x : take (n-1) xs take n (x:xs) | n > 0 = x : take (minusInt n 1) xs
take _ _ = errorNegativeIdx "take" take _ _ = errorNegativeIdx "take"
drop :: Int -> [a] -> [a] drop :: Int -> [a] -> [a]
drop 0 xs = xs drop 0 xs = xs
drop _ [] = [] drop _ [] = []
drop n (_:xs) | n > 0 = drop (n-1) xs drop n (_:xs) | n > 0 = drop (minusInt n 1) xs
drop _ _ = errorNegativeIdx "drop" drop _ _ = errorNegativeIdx "drop"
splitAt :: Int -> [a] -> ([a],[a]) splitAt :: Int -> [a] -> ([a],[a])
splitAt 0 xs = ([],xs) splitAt 0 xs = ([],xs)
splitAt _ [] = ([],[]) splitAt _ [] = ([],[])
splitAt n (x:xs) | n > 0 = (x:xs',xs'') where (xs',xs'') = splitAt (n-1) xs splitAt n (x:xs) | n > 0 = (x:xs',xs'') where (xs',xs'') = splitAt (minusInt n 1) xs
splitAt _ _ = errorNegativeIdx "splitAt" splitAt _ _ = errorNegativeIdx "splitAt"
#else /* hack away */ #else /* hack away */
...@@ -429,7 +435,7 @@ concat = foldr (++) [] ...@@ -429,7 +435,7 @@ concat = foldr (++) []
(!!) :: [a] -> Int -> a (!!) :: [a] -> Int -> a
#ifdef USE_REPORT_PRELUDE #ifdef USE_REPORT_PRELUDE
(x:_) !! 0 = x (x:_) !! 0 = x
(_:xs) !! n | n > 0 = xs !! (n-1) (_:xs) !! n | n > 0 = xs !! (minusInt n 1)
(_:_) !! _ = error "Prelude.(!!): negative index" (_:_) !! _ = error "Prelude.(!!): negative index"
[] !! _ = error "Prelude.(!!): index too large" [] !! _ = error "Prelude.(!!): index too large"
#else #else
......
...@@ -569,7 +569,11 @@ prR n r e0 ...@@ -569,7 +569,11 @@ prR n r e0
s@(h:t) = show ((round (r * 10^n))::Integer) s@(h:t) = show ((round (r * 10^n))::Integer)
e = e0+1 e = e0+1
#ifdef USE_REPORT_PRELUDE
takeN n ls rs = take n ls ++ rs
#else
takeN (I# n#) ls rs = takeUInt_append n# ls rs takeN (I# n#) ls rs = takeUInt_append n# ls rs
#endif
drop0 :: String -> String -> String drop0 :: String -> String -> String
drop0 [] rs = rs drop0 [] rs = rs
......
...@@ -32,7 +32,11 @@ module PrelShow ...@@ -32,7 +32,11 @@ module PrelShow
import {-# SOURCE #-} PrelErr ( error ) import {-# SOURCE #-} PrelErr ( error )
import PrelBase import PrelBase
import PrelMaybe import PrelMaybe
import PrelList ( (!!), break, dropWhile ) import PrelList ( (!!), break, dropWhile
#ifdef USE_REPORT_PRELUDE
, concatMap, foldr1
#endif
)
\end{code} \end{code}
......
...@@ -68,7 +68,10 @@ module Prelude ( ...@@ -68,7 +68,10 @@ module Prelude (
) where ) where
import PrelBase import PrelBase
import PrelList hiding ( takeUInt_append ) import PrelList
#ifndef USE_REPORT_PRELUDE
hiding ( takeUInt_append )
#endif
import PrelRead import PrelRead
import PrelEnum import PrelEnum
import PrelNum import PrelNum
......
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