From fc0ea62713a45e0004927195946746c1bcebe0ef Mon Sep 17 00:00:00 2001
From: sof <unknown>
Date: Mon, 1 Feb 1999 10:02:18 +0000
Subject: [PATCH] [project @ 1999-02-01 10:02:15 by sof] H98 Prelude tweaks

---
 ghc/lib/std/Directory.lhs         |  7 ++++++-
 ghc/lib/std/Ix.lhs                | 14 +++++++-------
 ghc/lib/std/PrelArr.lhs           |  2 +-
 ghc/lib/std/PrelBase.lhs          |  6 +++---
 ghc/lib/std/PrelException.hi-boot |  2 +-
 ghc/lib/std/PrelNum.lhs           |  2 +-
 ghc/lib/std/PrelNumExtra.lhs      |  1 +
 ghc/lib/std/Prelude.lhs           |  2 +-
 8 files changed, 21 insertions(+), 15 deletions(-)

diff --git a/ghc/lib/std/Directory.lhs b/ghc/lib/std/Directory.lhs
index 263aeca7e4d6..fb76a2efefda 100644
--- a/ghc/lib/std/Directory.lhs
+++ b/ghc/lib/std/Directory.lhs
@@ -20,7 +20,12 @@ are relative to the current directory.
 {-# OPTIONS -#include <sys/stat.h> -#include <dirent.h> -#include "cbits/stgio.h" #-}
 module Directory 
    ( 
-      Permissions(Permissions,readable,writable,executable,searchable)
+      Permissions               -- abstract
+      
+    , readable                  -- :: Permissions -> Bool
+    , writable                  -- :: Permissions -> Bool
+    , executable                -- :: Permissions -> Bool
+    , searchable                -- :: Permissions -> Bool
 
     , createDirectory		-- :: FilePath -> IO ()
     , removeDirectory		-- :: FilePath -> IO ()
diff --git a/ghc/lib/std/Ix.lhs b/ghc/lib/std/Ix.lhs
index 545c266f43bf..5f121d854239 100644
--- a/ghc/lib/std/Ix.lhs
+++ b/ghc/lib/std/Ix.lhs
@@ -41,7 +41,7 @@ import PrelBase
 %*********************************************************
 
 \begin{code}
-class  ({-Show a,-} Ord a) => Ix a  where
+class  (Ord a) => Ix a  where
     range		:: (a,a) -> [a]
     index		:: (a,a) -> a -> Int
     inRange		:: (a,a) -> a -> Bool
@@ -56,16 +56,16 @@ class  ({-Show a,-} Ord a) => Ix a  where
 
 \begin{code}
 instance  Ix Char  where
-    range (c,c')
-      | c <= c'  	=  [c..c']
+    range (m,n)
+      | m <= n  	=  [m..n]
       | otherwise       =  []
-    index b@(c,_) ci
-	| inRange b ci	=  fromEnum ci - fromEnum c
-	| otherwise	=  indexError ci b "Char"
+    index b@(m,_) i
+	| inRange b i	=  fromEnum i - fromEnum m
+	| otherwise	=  indexError i b "Char"
     inRange (m,n) i	=  m <= i && i <= n
 
 instance  Ix Int  where
-    range (m,n)		
+    range (m,n)
       | m <= n	        =  [m..n]
       | otherwise       =  []
     index b@(m,_) i
diff --git a/ghc/lib/std/PrelArr.lhs b/ghc/lib/std/PrelArr.lhs
index 4f4d89ef8874..51508a352068 100644
--- a/ghc/lib/std/PrelArr.lhs
+++ b/ghc/lib/std/PrelArr.lhs
@@ -128,7 +128,7 @@ array ixs ivs =
 	case (new_array_thing s)		of { (# s#, arr@(MutableArray _ arr#) #) ->
 	let
 	 fill_in s1# [] = s1#
-	 fill_in s1# ((i,v):is) =
+	 fill_in s1# ((i,v) : is) =
 		case (index ixs i)	        of { I# n# ->
 		case writeArray# arr# n# v s1#  of { s2# -> 
 		fill_in s2# is }}
diff --git a/ghc/lib/std/PrelBase.lhs b/ghc/lib/std/PrelBase.lhs
index 1d6d69dbc78f..8ff06b7fe863 100644
--- a/ghc/lib/std/PrelBase.lhs
+++ b/ghc/lib/std/PrelBase.lhs
@@ -377,7 +377,7 @@ instance  Enum Char  where
     enumFrom   (C# c)	       = efttCh (ord# c)  1#   (># 255#)
     enumFromTo (C# c1) (C# c2) 
         | c1 `leChar#` c2 = efttCh (ord# c1) 1#               (># (ord# c2))
-        | otherwise       = efttCh (ord# c1) (negateInt# 1#)  (<# (ord# c2))
+        | otherwise       = []
 
     enumFromThen (C# c1) (C# c2)
 	| c1 `leChar#` c2 = efttCh (ord# c1) (ord# c2 -# ord# c1) (># 255#)
@@ -521,8 +521,8 @@ instance  Enum Int  where
     enumFrom     (I# c)	= efttInt True c 1# (\ _ -> False)
 
     enumFromTo   (I# c1) (I# c2) 
-        | c1 <# c2  = efttInt True  c1 1#              (># c2)
-	| otherwise = efttInt False c1 (negateInt# 1#) (<# c2)
+        | c1 <=# c2 = efttInt True  c1 1#              (># c2)
+	| otherwise = []
 
     enumFromThen (I# c1) (I# c2) 
         | c1 <# c2  = efttInt True  c1 (c2 -# c1) (\ _ -> False)
diff --git a/ghc/lib/std/PrelException.hi-boot b/ghc/lib/std/PrelException.hi-boot
index 99cbf7995674..85561ba42abc 100644
--- a/ghc/lib/std/PrelException.hi-boot
+++ b/ghc/lib/std/PrelException.hi-boot
@@ -5,7 +5,7 @@
 --	for PrelException.hi.
 ---------------------------------------------------------------------------
  
-__interface PrelErr 1 where
+__interface PrelException 1 where
 __export ! PrelException ioError catch;
 1 ioError :: __forall [a] => PrelIOBase.IOError -> PrelIOBase.IO a ;
 1 catch :: __forall [a] => PrelIOBase.IO a -> (PrelIOBase.IOError -> PrelIOBase.IO a) -> PrelIOBase.IO a ;
diff --git a/ghc/lib/std/PrelNum.lhs b/ghc/lib/std/PrelNum.lhs
index 08081353f35d..70e826c37a11 100644
--- a/ghc/lib/std/PrelNum.lhs
+++ b/ghc/lib/std/PrelNum.lhs
@@ -276,7 +276,7 @@ instance  Enum Integer  where
 	                    where en' a b = a : en' (a + b) b
     enumFromTo n m
       | n <= m           =  takeWhile (<= m) (enumFrom n)
-      | otherwise        =  takeWhile (>= m) (enumFromThen n (n-1))
+      | otherwise        =  []
     enumFromThenTo n m p =  takeWhile pred   (enumFromThen n m)
 	    where
 	     pred | m >= n    = (<= p)
diff --git a/ghc/lib/std/PrelNumExtra.lhs b/ghc/lib/std/PrelNumExtra.lhs
index 8322e260de1a..265f76cafaed 100644
--- a/ghc/lib/std/PrelNumExtra.lhs
+++ b/ghc/lib/std/PrelNumExtra.lhs
@@ -394,6 +394,7 @@ instance  Enum Double  where
     toEnum         =  fromIntegral
     fromEnum       =  fromInteger . truncate   -- may overflow
     enumFrom	   =  numericEnumFrom
+    enumFromTo     =  numericEnumFromTo
     enumFromThen   =  numericEnumFromThen
     enumFromThenTo =  numericEnumFromThenTo
 
diff --git a/ghc/lib/std/Prelude.lhs b/ghc/lib/std/Prelude.lhs
index 236558c35ee2..6ba2bd55e6e4 100644
--- a/ghc/lib/std/Prelude.lhs
+++ b/ghc/lib/std/Prelude.lhs
@@ -29,7 +29,7 @@ module Prelude (
     Either(..),
     Ordering(..), 
     Char, String, Int, Integer, Float, Double, IO,
-    Ratio, Rational, 
+    Rational,
     []((:), []),
     
     module PrelTup,
-- 
GitLab