From cfba89544a1b88f650bf70c05b4edd03972c0cf2 Mon Sep 17 00:00:00 2001
From: sof <unknown>
Date: Thu, 27 Aug 1998 12:55:58 +0000
Subject: [PATCH] [project @ 1998-08-27 12:55:57 by sof] FilePath moved from
 PrelHandle to PrelIOBase

---
 ghc/lib/std/PrelHandle.lhs | 4 +---
 ghc/lib/std/PrelIOBase.lhs | 9 ++++++++-
 2 files changed, 9 insertions(+), 4 deletions(-)

diff --git a/ghc/lib/std/PrelHandle.lhs b/ghc/lib/std/PrelHandle.lhs
index 4fa4a7d45bd4..6d7a6c96282a 100644
--- a/ghc/lib/std/PrelHandle.lhs
+++ b/ghc/lib/std/PrelHandle.lhs
@@ -35,15 +35,13 @@ import PrelConc				-- concurrent only
 
 %*********************************************************
 %*							*
-\subsection{Types @FilePath@, @Handle@, @Handle__@}
+\subsection{Types @Handle@, @Handle__@}
 %*							*
 %*********************************************************
 
 The @Handle@ and @Handle__@ types are defined in @IOBase@.
 
 \begin{code}
-type FilePath = String
-
 {-# INLINE newHandle   #-}
 {-# INLINE readHandle  #-}
 {-# INLINE writeHandle #-}
diff --git a/ghc/lib/std/PrelIOBase.lhs b/ghc/lib/std/PrelIOBase.lhs
index fe137694d83c..56b7d337ba7d 100644
--- a/ghc/lib/std/PrelIOBase.lhs
+++ b/ghc/lib/std/PrelIOBase.lhs
@@ -291,6 +291,13 @@ constructErrorMsg call_site reason =
  return (IOError Nothing iot call_site msg)
 \end{code}
 
+File names are specified using @FilePath@, a OS-dependent
+string that (hopefully, I guess) maps to an accessible file/object.
+
+\begin{code}
+type FilePath = String
+\end{code}
+
 %*********************************************************
 %*							*
 \subsection{Types @Handle@, @Handle__@}
@@ -367,7 +374,7 @@ data Handle__
       haFO__	      :: FILE_OBJECT,
       haType__        :: Handle__Type,
       haBufferMode__  :: BufferMode,
-      haFilePath__    :: String
+      haFilePath__    :: FilePath
     }      
 
 {-
-- 
GitLab