Skip to content
Snippets Groups Projects
Commit cfba8954 authored by sof's avatar sof
Browse files

[project @ 1998-08-27 12:55:57 by sof]

FilePath moved from PrelHandle to PrelIOBase
parent 6c76fdf9
No related merge requests found
......@@ -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 #-}
......
......@@ -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
}
{-
......
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