summaryrefslogtreecommitdiff
path: root/ghc/misc
diff options
context:
space:
mode:
authorpartain <unknown>1996-07-26 21:29:20 +0000
committerpartain <unknown>1996-07-26 21:29:20 +0000
commit216bfb01a138932092eab3076c85648f5eee99b3 (patch)
treeb045882217811761a5d7b67360748a3e78cc89d5 /ghc/misc
parent5eb1c77c795f92ed0f4c8023847e9d4be1a4fd0d (diff)
downloadhaskell-216bfb01a138932092eab3076c85648f5eee99b3.tar.gz
[project @ 1996-07-26 20:58:52 by partain]
Final changes for 2.01
Diffstat (limited to 'ghc/misc')
-rw-r--r--ghc/misc/examples/io/io002/Main.hs2
-rw-r--r--ghc/misc/examples/io/io003/Main.hs2
-rw-r--r--ghc/misc/examples/io/io004/Main.hs2
-rw-r--r--ghc/misc/examples/io/io005/Main.hs6
-rw-r--r--ghc/misc/examples/io/io006/Main.hs4
-rw-r--r--ghc/misc/examples/io/io007/Main.hs9
-rw-r--r--ghc/misc/examples/io/io008/Main.hs9
-rw-r--r--ghc/misc/examples/io/io009/Main.hs5
-rw-r--r--ghc/misc/examples/io/io010/Main.hs2
-rw-r--r--ghc/misc/examples/io/io011/Main.hs4
-rw-r--r--ghc/misc/examples/io/io012/Main.hs9
-rw-r--r--ghc/misc/examples/io/io013/Main.hs6
-rw-r--r--ghc/misc/examples/io/io014/Main.hs28
-rw-r--r--ghc/misc/examples/io/io015/Main.hs2
-rw-r--r--ghc/misc/examples/io/io016/Main.hs5
-rw-r--r--ghc/misc/examples/io/io017/Main.hs2
-rw-r--r--ghc/misc/examples/io/io018/Main.hs4
-rw-r--r--ghc/misc/examples/io/io019/Main.hs7
-rw-r--r--ghc/misc/examples/io/io020/Main.hs6
-rw-r--r--ghc/misc/examples/io/io021/Main.hs2
-rw-r--r--ghc/misc/examples/posix/po001/Main.hs10
-rw-r--r--ghc/misc/examples/posix/po002/Main.hs2
-rw-r--r--ghc/misc/examples/posix/po003/Main.hs4
-rw-r--r--ghc/misc/examples/posix/po004/Main.hs14
-rw-r--r--ghc/misc/examples/posix/po005/Main.hs14
-rw-r--r--ghc/misc/examples/posix/po006/Main.hs8
-rw-r--r--ghc/misc/examples/posix/po007/Main.hs4
-rw-r--r--ghc/misc/examples/posix/po008/Main.hs2
-rw-r--r--ghc/misc/examples/posix/po009/Main.hs4
-rw-r--r--ghc/misc/examples/posix/po010/Main.hs4
-rw-r--r--ghc/misc/examples/posix/po011/Main.hs4
-rw-r--r--ghc/misc/examples/posix/po012/Main.hs3
32 files changed, 106 insertions, 83 deletions
diff --git a/ghc/misc/examples/io/io002/Main.hs b/ghc/misc/examples/io/io002/Main.hs
index 346bffb8a1..c9a1bcfa82 100644
--- a/ghc/misc/examples/io/io002/Main.hs
+++ b/ghc/misc/examples/io/io002/Main.hs
@@ -1,4 +1,4 @@
-import LibSystem (getEnv)
+import System (getEnv)
main =
getEnv "TERM" >>= \ term ->
diff --git a/ghc/misc/examples/io/io003/Main.hs b/ghc/misc/examples/io/io003/Main.hs
index 535b4716df..93fff71be5 100644
--- a/ghc/misc/examples/io/io003/Main.hs
+++ b/ghc/misc/examples/io/io003/Main.hs
@@ -1,4 +1,4 @@
-import LibSystem (getProgName, getArgs)
+import System (getProgName, getArgs)
main =
getProgName >>= \ argv0 ->
diff --git a/ghc/misc/examples/io/io004/Main.hs b/ghc/misc/examples/io/io004/Main.hs
index 59c745d4b1..69d2221743 100644
--- a/ghc/misc/examples/io/io004/Main.hs
+++ b/ghc/misc/examples/io/io004/Main.hs
@@ -1,3 +1,3 @@
-import LibSystem (exitWith, ExitCode(..))
+import System (exitWith, ExitCode(..))
main = exitWith (ExitFailure 42)
diff --git a/ghc/misc/examples/io/io005/Main.hs b/ghc/misc/examples/io/io005/Main.hs
index a987b9fb27..3a41560df6 100644
--- a/ghc/misc/examples/io/io005/Main.hs
+++ b/ghc/misc/examples/io/io005/Main.hs
@@ -1,11 +1,11 @@
-import LibSystem (system, ExitCode(..), exitWith)
+import System (system, ExitCode(..), exitWith)
main =
system "cat dog 1>/dev/null 2>&1" >>= \ ec ->
case ec of
- ExitSuccess -> putStr "What?!?\n" >> fail "dog succeeded"
+ ExitSuccess -> putStr "What?!?\n" >> fail (userError "dog succeeded")
ExitFailure _ ->
system "cat Main.hs 2>/dev/null" >>= \ ec ->
case ec of
ExitSuccess -> exitWith ExitSuccess
- ExitFailure _ -> putStr "What?!?\n" >> fail "cat failed"
+ ExitFailure _ -> putStr "What?!?\n" >> fail (userError "cat failed")
diff --git a/ghc/misc/examples/io/io006/Main.hs b/ghc/misc/examples/io/io006/Main.hs
index c6fc5394e3..6eb862c3da 100644
--- a/ghc/misc/examples/io/io006/Main.hs
+++ b/ghc/misc/examples/io/io006/Main.hs
@@ -1,4 +1,6 @@
+import IO -- 1.3
+
main =
hClose stderr >>
- hPutStr stderr "junk" `handle` \ (IllegalOperation _) -> putStr "Okay\n"
+ hPutStr stderr "junk" `catch` \ err -> if isIllegalOperation err then putStr "Okay\n" else error "Not okay\n"
diff --git a/ghc/misc/examples/io/io007/Main.hs b/ghc/misc/examples/io/io007/Main.hs
index d6c94d8ef7..467382ff76 100644
--- a/ghc/misc/examples/io/io007/Main.hs
+++ b/ghc/misc/examples/io/io007/Main.hs
@@ -1,6 +1,11 @@
+import IO -- 1.3
+
main =
openFile "io007.in" ReadMode >>= \ hIn ->
- hPutStr hIn "test" `handle`
- \ (IllegalOperation _) ->
+ hPutStr hIn "test" `catch`
+ \ err ->
+ if isIllegalOperation err then
hGetContents hIn >>= \ stuff ->
hPutStr stdout stuff
+ else
+ error "Oh dear\n"
diff --git a/ghc/misc/examples/io/io008/Main.hs b/ghc/misc/examples/io/io008/Main.hs
index 51685c9201..47f1a6ea97 100644
--- a/ghc/misc/examples/io/io008/Main.hs
+++ b/ghc/misc/examples/io/io008/Main.hs
@@ -1,4 +1,7 @@
-import LibDirectory (removeFile)
+import IO -- 1.3
+import GHCio
+
+import Directory (removeFile)
main =
openFile "io008.in" ReadMode >>= \ hIn ->
@@ -14,5 +17,5 @@ main =
copy :: Handle -> Handle -> IO ()
copy hIn hOut =
- try (hGetChar hIn) >>=
- either (\ EOF -> return ()) ( \ x -> hPutChar hOut x >> copy hIn hOut)
+ tryIO (hGetChar hIn) >>=
+ either (\ err -> if isEOFError err then return () else error "copy") ( \ x -> hPutChar hOut x >> copy hIn hOut)
diff --git a/ghc/misc/examples/io/io009/Main.hs b/ghc/misc/examples/io/io009/Main.hs
index b1bc0f2dc3..5f95ce0c42 100644
--- a/ghc/misc/examples/io/io009/Main.hs
+++ b/ghc/misc/examples/io/io009/Main.hs
@@ -1,7 +1,6 @@
-import LibDirectory (getDirectoryContents)
+import Directory (getDirectoryContents)
import QSort (sort)
main =
getDirectoryContents "." >>= \ names ->
- putText (sort names) >>
- putChar '\n' \ No newline at end of file
+ print (sort names)
diff --git a/ghc/misc/examples/io/io010/Main.hs b/ghc/misc/examples/io/io010/Main.hs
index 5e5b0c3d16..764290c754 100644
--- a/ghc/misc/examples/io/io010/Main.hs
+++ b/ghc/misc/examples/io/io010/Main.hs
@@ -17,4 +17,4 @@ main =
dot :: String -> Bool
dot "." = True
dot ".." = True
-dot _ = False \ No newline at end of file
+dot _ = False
diff --git a/ghc/misc/examples/io/io011/Main.hs b/ghc/misc/examples/io/io011/Main.hs
index 2fcbce5cb5..97f7d90e58 100644
--- a/ghc/misc/examples/io/io011/Main.hs
+++ b/ghc/misc/examples/io/io011/Main.hs
@@ -1,4 +1,6 @@
-import LibDirectory
+import IO -- 1.3
+
+import Directory
main =
createDirectory "foo" >>
diff --git a/ghc/misc/examples/io/io012/Main.hs b/ghc/misc/examples/io/io012/Main.hs
index 9b7fba3925..c5a16b730a 100644
--- a/ghc/misc/examples/io/io012/Main.hs
+++ b/ghc/misc/examples/io/io012/Main.hs
@@ -1,11 +1,12 @@
-import LibCPUTime
+import IO -- 1.3
+
+import CPUTime
main =
openFile "/dev/null" WriteMode >>= \ h ->
- hPutText h (nfib 30) >>
+ hPrint h (nfib 30) >>
getCPUTime >>= \ t ->
- putText t >>
- putChar '\n'
+ print t
nfib :: Integer -> Integer
nfib n
diff --git a/ghc/misc/examples/io/io013/Main.hs b/ghc/misc/examples/io/io013/Main.hs
index 39c429e13d..9598e04d61 100644
--- a/ghc/misc/examples/io/io013/Main.hs
+++ b/ghc/misc/examples/io/io013/Main.hs
@@ -1,8 +1,9 @@
+import IO -- 1.3
+
main =
openFile "io013.in" ReadMode >>= \ h ->
hFileSize h >>= \ sz ->
- putText sz >>
- putChar '\n' >>
+ print sz >>
hSeek h SeekFromEnd (-3) >>
hGetChar h >>= \ x ->
putStr (x:"\n") >>
@@ -14,4 +15,3 @@ main =
openFile "/dev/null" ReadMode >>= \ h ->
hIsSeekable h >>= \ False ->
hClose h
- \ No newline at end of file
diff --git a/ghc/misc/examples/io/io014/Main.hs b/ghc/misc/examples/io/io014/Main.hs
index 23f62ca748..fecf4a51d7 100644
--- a/ghc/misc/examples/io/io014/Main.hs
+++ b/ghc/misc/examples/io/io014/Main.hs
@@ -1,22 +1,22 @@
+import IO -- 1.3
+
main =
accumulate (map hIsOpen [stdin, stdout, stderr]) >>= \ opens ->
- putText opens >>
- putChar '\n' >>
+ print opens >>
accumulate (map hIsClosed [stdin, stdout, stderr]) >>= \ closeds ->
- putText closeds >>
- putChar '\n' >>
+ print closeds >>
accumulate (map hIsReadable [stdin, stdout, stderr]) >>= \ readables ->
- putText readables >>
- putChar '\n' >>
+ print readables >>
accumulate (map hIsWritable [stdin, stdout, stderr]) >>= \ writables ->
- putText writables >>
- putChar '\n' >>
+ print writables >>
accumulate (map hIsBlockBuffered [stdin, stdout, stderr]) >>= \ buffereds ->
- putText buffereds >>
- putChar '\n' >>
+ print buffereds >>
accumulate (map hIsLineBuffered [stdin, stdout, stderr]) >>= \ buffereds ->
- putText buffereds >>
- putChar '\n' >>
+ print buffereds >>
accumulate (map hIsNotBuffered [stdin, stdout, stderr]) >>= \ buffereds ->
- putText buffereds >>
- putChar '\n'
+ print buffereds
+ where
+ -- these didn't make it into 1.3
+ hIsBlockBuffered h = hGetBuffering h >>= \ b -> return $ case b of { BlockBuffering _ -> True; _ -> False }
+ hIsLineBuffered h = hGetBuffering h >>= \ b -> return $ case b of { LineBuffering -> True; _ -> False }
+ hIsNotBuffered h = hGetBuffering h >>= \ b -> return $ case b of { NoBuffering -> True; _ -> False }
diff --git a/ghc/misc/examples/io/io015/Main.hs b/ghc/misc/examples/io/io015/Main.hs
index a58450942c..37f0cc134a 100644
--- a/ghc/misc/examples/io/io015/Main.hs
+++ b/ghc/misc/examples/io/io015/Main.hs
@@ -1,3 +1,5 @@
+import IO -- 1.3
+
main =
isEOF >>= \ eof ->
if eof then
diff --git a/ghc/misc/examples/io/io016/Main.hs b/ghc/misc/examples/io/io016/Main.hs
index e8df7a93dd..1ce01b2d45 100644
--- a/ghc/misc/examples/io/io016/Main.hs
+++ b/ghc/misc/examples/io/io016/Main.hs
@@ -1,4 +1,7 @@
-import LibSystem (getArgs)
+import IO -- 1.3
+
+import System (getArgs)
+import Char (toUpper)
main = getArgs >>= \ [f1,f2] ->
openFile f1 ReadMode >>= \ h1 ->
diff --git a/ghc/misc/examples/io/io017/Main.hs b/ghc/misc/examples/io/io017/Main.hs
index f0a6d3ef3b..2be725480b 100644
--- a/ghc/misc/examples/io/io017/Main.hs
+++ b/ghc/misc/examples/io/io017/Main.hs
@@ -1,3 +1,5 @@
+import IO -- 1.3
+
main =
hSetBuffering stdout NoBuffering >>
putStr "Enter an integer: " >>
diff --git a/ghc/misc/examples/io/io018/Main.hs b/ghc/misc/examples/io/io018/Main.hs
index f15c1cb5c1..7318cc7ac9 100644
--- a/ghc/misc/examples/io/io018/Main.hs
+++ b/ghc/misc/examples/io/io018/Main.hs
@@ -1,4 +1,6 @@
-import LibSystem(getArgs)
+import IO -- 1.3
+
+import System(getArgs)
main = getArgs >>= \ [user,host] ->
let username = (user ++ "@" ++ host) in
diff --git a/ghc/misc/examples/io/io019/Main.hs b/ghc/misc/examples/io/io019/Main.hs
index 168a4ac249..bd50838bb5 100644
--- a/ghc/misc/examples/io/io019/Main.hs
+++ b/ghc/misc/examples/io/io019/Main.hs
@@ -1,9 +1,8 @@
-import LibTime
+import Time
main =
getClockTime >>= \ time ->
- putText time >>
- putChar '\n' >>
+ print time >>
let (CalendarTime year month mday hour min sec psec
wday yday timezone gmtoff isdst) = toUTCTime time
@@ -20,4 +19,4 @@ main =
shows2 x = showString (pad2 x)
pad2 x = case show x of
c@[_] -> '0' : c
- cs -> cs \ No newline at end of file
+ cs -> cs
diff --git a/ghc/misc/examples/io/io020/Main.hs b/ghc/misc/examples/io/io020/Main.hs
index ff68bd9f35..1f349ebd32 100644
--- a/ghc/misc/examples/io/io020/Main.hs
+++ b/ghc/misc/examples/io/io020/Main.hs
@@ -1,4 +1,4 @@
-import LibTime
+import Time
main =
getClockTime >>= \ time ->
@@ -7,7 +7,7 @@ main =
time' = toClockTime (CalendarTime (year - 1) month mday hour min sec psec
wday yday timezone gmtoff isdst)
in
- putText time >>
+ print time >>
putChar '\n' >>
- putText time' >>
+ print time' >>
putChar '\n'
diff --git a/ghc/misc/examples/io/io021/Main.hs b/ghc/misc/examples/io/io021/Main.hs
index 66548f63ee..c45a40b9b1 100644
--- a/ghc/misc/examples/io/io021/Main.hs
+++ b/ghc/misc/examples/io/io021/Main.hs
@@ -1,3 +1,5 @@
+import IO -- 1.3
+
main =
hSetBuffering stdin NoBuffering >>
hSetBuffering stdout NoBuffering >>
diff --git a/ghc/misc/examples/posix/po001/Main.hs b/ghc/misc/examples/posix/po001/Main.hs
index db10babaa4..31c32ba94f 100644
--- a/ghc/misc/examples/posix/po001/Main.hs
+++ b/ghc/misc/examples/posix/po001/Main.hs
@@ -1,14 +1,14 @@
-import LibPosix
+import Posix
main =
getParentProcessID >>= \ ppid ->
getProcessID >>= \ pid ->
putStr "Parent Process ID: " >>
- putText ppid >>
+ print ppid >>
putStr "\nProcess ID: " >>
- putText pid >>
+ print pid >>
putStr "\nforking ps uxww" >>
- putText ppid >>
+ print ppid >>
putChar '\n' >>
forkProcess >>= \ child ->
case child of
@@ -18,6 +18,6 @@ main =
doParent cpid pid =
getProcessStatus True False cpid >>
putStr "\nChild finished. Now exec'ing ps uxww" >>
- putText pid >>
+ print pid >>
putChar '\n' >>
executeFile "ps" True ["uxww" ++ show pid] Nothing
diff --git a/ghc/misc/examples/posix/po002/Main.hs b/ghc/misc/examples/posix/po002/Main.hs
index e646f02839..8d01e8b69f 100644
--- a/ghc/misc/examples/posix/po002/Main.hs
+++ b/ghc/misc/examples/posix/po002/Main.hs
@@ -1,4 +1,4 @@
-import LibPosix
+import Posix
main =
executeFile "printenv" True [] (Just [("ONE","1"),("TWO","2")])
diff --git a/ghc/misc/examples/posix/po003/Main.hs b/ghc/misc/examples/posix/po003/Main.hs
index b05d9cf7f0..eed6c08456 100644
--- a/ghc/misc/examples/posix/po003/Main.hs
+++ b/ghc/misc/examples/posix/po003/Main.hs
@@ -1,5 +1,5 @@
-import LibPosix
+import Posix
main =
openFile "po003.out" WriteMode >>= \ h ->
- runProcess "pwd" [] Nothing (Just "/usr/tmp") Nothing (Just h) Nothing \ No newline at end of file
+ runProcess "pwd" [] Nothing (Just "/usr/tmp") Nothing (Just h) Nothing
diff --git a/ghc/misc/examples/posix/po004/Main.hs b/ghc/misc/examples/posix/po004/Main.hs
index 1725dd4e2b..2423f3f77a 100644
--- a/ghc/misc/examples/posix/po004/Main.hs
+++ b/ghc/misc/examples/posix/po004/Main.hs
@@ -1,5 +1,5 @@
-import LibPosix
-import LibSystem(ExitCode(..), exitWith)
+import Posix
+import System(ExitCode(..), exitWith)
main =
forkProcess >>= \ maybe_pid ->
@@ -11,7 +11,7 @@ doParent =
getAnyProcessStatus True False >>= \ (Just (pid, tc)) ->
case tc of
Terminated sig | sig == floatingPointException -> forkChild2
- _ -> fail "unexpected termination cause"
+ _ -> fail (userError "unexpected termination cause")
forkChild2 =
forkProcess >>= \ maybe_pid ->
@@ -23,7 +23,7 @@ doParent2 =
getAnyProcessStatus True False >>= \ (Just (pid, tc)) ->
case tc of
Exited (ExitFailure 42) -> forkChild3
- _ -> fail "unexpected termination cause (2)"
+ _ -> fail (userError "unexpected termination cause (2)")
forkChild3 =
forkProcess >>= \ maybe_pid ->
@@ -35,7 +35,7 @@ doParent3 =
getAnyProcessStatus True False >>= \ (Just (pid, tc)) ->
case tc of
Exited ExitSuccess -> forkChild4
- _ -> fail "unexpected termination cause (3)"
+ _ -> fail (userError "unexpected termination cause (3)")
forkChild4 =
forkProcess >>= \ maybe_pid ->
@@ -47,12 +47,12 @@ doParent4 =
getAnyProcessStatus True True >>= \ (Just (pid, tc)) ->
case tc of
Stopped sig | sig == softwareStop -> enoughAlready pid
- _ -> fail "unexpected termination cause (4)"
+ _ -> fail (userError "unexpected termination cause (4)")
enoughAlready pid =
signalProcess killProcess pid >>
getAnyProcessStatus True True >>= \ (Just (pid, tc)) ->
case tc of
Terminated sig | sig == killProcess -> putStr "I'm happy.\n"
- _ -> fail "unexpected termination cause (5)"
+ _ -> fail (userError "unexpected termination cause (5)")
diff --git a/ghc/misc/examples/posix/po005/Main.hs b/ghc/misc/examples/posix/po005/Main.hs
index 8ea76255e1..81dce3ae02 100644
--- a/ghc/misc/examples/posix/po005/Main.hs
+++ b/ghc/misc/examples/posix/po005/Main.hs
@@ -1,4 +1,4 @@
-import LibPosix
+import Posix
main =
getEnvVar "TERM" >>= \ term ->
@@ -6,25 +6,25 @@ main =
putChar '\n' >>
setEnvironment [("one","1"),("two","2")] >>
getEnvironment >>= \ env ->
- putText env >>
+ print env >>
putChar '\n' >>
setEnvVar "foo" "bar" >>
getEnvironment >>= \ env ->
- putText env >>
+ print env >>
putChar '\n' >>
setEnvVar "foo" "baz" >>
getEnvironment >>= \ env ->
- putText env >>
+ print env >>
putChar '\n' >>
setEnvVar "fu" "bar" >>
getEnvironment >>= \ env ->
- putText env >>
+ print env >>
putChar '\n' >>
removeEnvVar "foo" >>
getEnvironment >>= \ env ->
- putText env >>
+ print env >>
putChar '\n' >>
setEnvironment [] >>
getEnvironment >>= \ env ->
- putText env >>
+ print env >>
putChar '\n'
diff --git a/ghc/misc/examples/posix/po006/Main.hs b/ghc/misc/examples/posix/po006/Main.hs
index 8008a50f2b..eb6451dd73 100644
--- a/ghc/misc/examples/posix/po006/Main.hs
+++ b/ghc/misc/examples/posix/po006/Main.hs
@@ -1,4 +1,4 @@
-import LibPosix
+import Posix
main =
epochTime >>= \ start ->
@@ -6,9 +6,9 @@ main =
let timeleft = 0 in
epochTime >>= \ finish ->
putStr "Started: " >>
- putText start >>
+ print start >>
putStr "\nSlept: " >>
- putText (5 - timeleft) >>
+ print (5 - timeleft) >>
putStr "\nFinished: " >>
- putText finish >>
+ print finish >>
putChar '\n'
diff --git a/ghc/misc/examples/posix/po007/Main.hs b/ghc/misc/examples/posix/po007/Main.hs
index d70e913e6b..3a37dc7545 100644
--- a/ghc/misc/examples/posix/po007/Main.hs
+++ b/ghc/misc/examples/posix/po007/Main.hs
@@ -1,4 +1,4 @@
-import LibPosix
+import Posix
main =
installHandler keyboardSignal (Catch doCtrlC) Nothing >>
@@ -28,4 +28,4 @@ doCtrlC =
ccStr '\DEL' = "^?"
ccStr x
| x >= ' ' = [x]
- | otherwise = ['^', (chr (ord x + ord '@'))]
+ | otherwise = ['^', (toEnum (fromEnum x + fromEnum '@'))]
diff --git a/ghc/misc/examples/posix/po008/Main.hs b/ghc/misc/examples/posix/po008/Main.hs
index c775064405..249e58eedc 100644
--- a/ghc/misc/examples/posix/po008/Main.hs
+++ b/ghc/misc/examples/posix/po008/Main.hs
@@ -1,4 +1,4 @@
-import LibPosix
+import Posix
main =
installHandler realTimeAlarm (Catch alarmclock) Nothing >>
diff --git a/ghc/misc/examples/posix/po009/Main.hs b/ghc/misc/examples/posix/po009/Main.hs
index 9707c58747..a1f284f78d 100644
--- a/ghc/misc/examples/posix/po009/Main.hs
+++ b/ghc/misc/examples/posix/po009/Main.hs
@@ -1,4 +1,4 @@
-import LibPosix
+import Posix
main =
putStr "Blocking real time alarms.\n" >>
@@ -9,6 +9,6 @@ main =
sleep 5 >>
getPendingSignals >>= \ ints ->
putStr "Checking pending interrupts for RealTimeAlarm\n" >>
- putText (inSignalSet realTimeAlarm ints) >>
+ print (inSignalSet realTimeAlarm ints) >>
putChar '\n'
diff --git a/ghc/misc/examples/posix/po010/Main.hs b/ghc/misc/examples/posix/po010/Main.hs
index bfc890941f..86ef3e1c24 100644
--- a/ghc/misc/examples/posix/po010/Main.hs
+++ b/ghc/misc/examples/posix/po010/Main.hs
@@ -1,4 +1,4 @@
-import LibPosix
+import Posix
main =
getUserEntryForName "mattson" >>= \ mattson ->
@@ -21,4 +21,4 @@ ue2String ue =
uid = userID ue
gid = userGroupID ue
home = homeDirectory ue
- shell = userShell ue \ No newline at end of file
+ shell = userShell ue
diff --git a/ghc/misc/examples/posix/po011/Main.hs b/ghc/misc/examples/posix/po011/Main.hs
index 3d78924157..f8baf1cbc2 100644
--- a/ghc/misc/examples/posix/po011/Main.hs
+++ b/ghc/misc/examples/posix/po011/Main.hs
@@ -1,4 +1,4 @@
-import LibPosix
+import Posix
main =
getGroupEntryForName "grasp" >>= \ grasp ->
@@ -19,4 +19,4 @@ ge2String ge =
where
name = groupName ge
gid = groupID ge
- members = foldr (\x y -> x ++ (',' : y)) "" (groupMembers ge) \ No newline at end of file
+ members = foldr (\x y -> x ++ (',' : y)) "" (groupMembers ge)
diff --git a/ghc/misc/examples/posix/po012/Main.hs b/ghc/misc/examples/posix/po012/Main.hs
index d4eb3841bf..b84fafabe9 100644
--- a/ghc/misc/examples/posix/po012/Main.hs
+++ b/ghc/misc/examples/posix/po012/Main.hs
@@ -1,4 +1,5 @@
-import LibPosix
+import Posix
+import IO -- 1.3
main =
createFile "po012.out" stdFileMode >>= \ fd ->