Providence Salumu
Can import foreign functions like this:
foreign import ccall unsafe "stdlib.h malloc"
c_malloc :: CSize -> IO (Ptr a)
foreign import ccall unsafe "stdlib.h free"
c_free :: Ptr a -> IO ()
ccall
says use C calling convention (also cplusplus
and few others)unsafe
promises the C function will not call back into Haskellunafe
faster than safe
, but gives undefined results if call triggers GC"
[static
] [c-header] [&
][c-name]"
static
optional unless c-name is dynamic
or wrapper
.h
file with the declaration (ignored by GHC)FunPtr
s)Char
, Int
, Double
, Float
, Bool
, Int8
, Int16
, Int32
, Int64
, Word8
, Word16
, Word32
, Word64
, Ptr
a
, FunPtr a
, and StablePtr a
type
or newtype
wrappers for basic types (CInt
, CChar
, etc.)data CInt
, but :i
in GHCI reveals truth.]()
(for functions returning void
)IO a
where a
is either of the above twoIO
if function has side effects or non-determinism
Okay to omit if it is a pure C function:
foreign import ccall unsafe "arpa/inet.h ntohl"
ntohl :: Word32 -> Word32
Haskell can't check C purity, so omitting IO
can cause problems
hsc2hs
How to access C constants and data structures?
struct mystruct {
char *name;
int value;
};
data MyStruct -- no constructors, just a placeholder
getValue :: Ptr MyStruct -> IO CInt
getValue ptr = peek $ ptr `plusPtr` 8 -- breaks on 32-bit arch
hsc2hs
is pre-processor that lets you compute C values
#include "myheader.h"
getValue ptr = peek $ ptr `plusPtr`
#{offset struct mystruct, value}
printf
template-hsc.h
on your system to see defs of #
commands#let
(like #define
w/o parens)We've seen a few functions that "return" any type
undefined :: a
error :: String -> a
These functions throw language-level exceptions
Control.Exception
as follows:import Prelude hiding (catch)
import Control.Exception
Prelude
has an old, less general version of catch
you should avoid (hiding
keyword prevents import of specific symbols)
Control.Exception
gives you access to the following symbols:
class (Typeable e, Show e) => Exception e where ...
throw :: Exception e => e -> a
throwIO :: Exception e => e -> IO a
catch :: Exception e => IO a -> (e -> IO a) -> IO a
{-# LANGUAGE DeriveDataTypeable #-}
import Prelude hiding (catch)
import Control.Exception
import Data.Typeable
data MyError = MyError String deriving (Show, Typeable)
instance Exception MyError
catcher :: IO a -> IO (Maybe a)
catcher action = fmap Just action `catch` handler
where handler (MyError msg) = do putStrLn msg; return Nothing
*Main> catcher $ readFile "/dev/null"
Just ""
*Main> catcher $ throwIO $ MyError "something bad"
something bad
Nothing
DeriveDataTypeable
language pragma (later lecture)handler
's type cannot be inferred (use constructor or type signature)
e@(SomeException _)
catches all exceptionscatcher
around an IO actionthrow
exceptions in pure code, yet catch
them only in IO
(error "one") + (error "two")
?catch
is restricted to the IO
MonadIn IO
, use throwIO
(not throw
) to make exception sequencing precise
do x <- throwIO (MyError "one") -- this exception thrown
y <- throwIO (MyError "two") -- this code not reached
Beware catch
only catches exceptions if code actually evaluated
pureCatcher :: a -> IO (Maybe a)
pureCatcher a = (a `seq` return (Just a))
`catch` \(SomeException _) -> return Nothing
*Main> pureCatcher (undefined :: String)
Nothing
*Main> pureCatcher (undefined:undefined :: String)
Just "*** Exception: Prelude.undefined
try
returns Right a
normally, Left e
if an exception occurred
try :: Exception e => IO a -> IO (Either e a)
finally
and onException
run an clean-up action
finally :: IO a -> IO b -> IO a -- cleanup always
onException :: IO a -> IO b -> IO a -- after exception
b
) is discardedcatchJust
catches only exceptions matching a predicate on value
catchJust :: Exception e =>
(e -> Maybe b) -> IO a -> (b -> IO a) -> IO a
readFileIfExists f = catchJust p (readFile f) (\_ -> return "")
where p e = if isDoesNotExistError e then Just e else Nothing
*Main> readFileIfExists "/nosuchfile"
""
*Main> readFileIfExists "/etc/shadow"
*** Exception: /etc/shadow: openFile: permission denied ...
IO
actions
IO
monadIO
also can't catch exceptionsMaybe
Monad, where can use Nothing
to indicate failureinstance Monad Maybe where
(Just x) >>= k = k x
Nothing >>= _ = Nothing
return = Just
fail _ = Nothing
fail
method called when bind pattern matches fail in do
block*Main> (do 1 <- return 2; return 3) :: Maybe Int
Nothing
Haskell implements user-level threads in Control.Concurrent
forkIO
call creates a new thread:
forkIO :: IO () -> IO ThreadId -- creates a new thread
A few other very useful thread functions:
throwTo :: Exception e => ThreadId -> e -> IO ()
killThread :: ThreadId -> IO () -- = flip throwTo ThreadKilled
threadDelay :: Int -> IO () -- sleeps for # of µsec
myThreadId :: IO ThreadId
IO
action, or abort after # of µsec
System.Timeout
has a slightly better version of this functionnewtype TimedOut = TimedOut UTCTime deriving (Eq, Show, Typeable)
instance Exception TimedOut
timeout :: Int -> IO a -> IO (Maybe a)
timeout usec action = do
-- Create unique exception val (for nested timeouts):
expired <- fmap TimedOut getCurrentTime
ptid <- myThreadId
let child = do threadDelay usec
throwTo ptid expired
parent = do ctid <- forkIO child
result <- action
killThread ctid
return $ Just result
catchJust (\e -> if e == expired then Just e else Nothing)
parent
(\_ -> return Nothing)
MVar
sThe MVar
type lets threads communicate via shared variables
MVar t
is a mutable variable of type t
that is either full or emptynewEmptyMVar :: IO (MVar a) -- create empty MVar
newMVar :: a -> IO (MVar a) -- create full MVar given val
takeMVar :: MVar a -> IO a
putMVar :: MVar a -> a -> IO ()
MVar
is full, takeMVar
makes it empty and returns former contentsMVar
is empty, putMVar
fills it with a valueMVar
or putting a full one puts thread to sleep until MVar
becomes availableMVar
MVar
callstryTakeMVar :: MVar a -> IO (Maybe a) -- Nothing if empty
tryPutMVar :: MVar a -> a -> IO Bool -- False if full
import Control.Concurrent
import Control.Exception
import Control.Monad
pingpong :: Bool -> Int -> IO ()
pingpong v n = do
mvc <- newEmptyMVar
mvp <- newEmptyMVar
let parent n | n > 0 = do when v $ putStr $ " " ++ show n
putMVar mvc n
takeMVar mvp >>= parent
| otherwise = return ()
child = do n <- takeMVar mvc
putMVar mvp (n - 1)
child
tid <- forkIO child
parent n `finally` killThread tid
when v $ putStrLn ""
*Main> pingpong True 10
10 9 8 7 6 5 4 3 2 1
import Criterion.Main
...
main :: IO ()
main = defaultMain [
bench "thread switch test" mybench
]
where mybench = pingpong False 10000
$ ghc -O pingpong.hs
[1 of 1] Compiling Main ( pingpong.hs, pingpong.o )
Linking pingpong ...
$ ./pingpong
...
benchmarking thread switch test
mean: 3.782984 ms, lb 3.770838 ms, ub 3.798160 ms, ci 0.950
std dev: 69.27807 us, lb 55.00853 us, ub 88.83503 us, ci 0.950
-threaded
to allow OS threads (pthread_create
) as wellforkOS
call creates Haskell thread bound to a new OS thread
forkOS :: IO () -> IO ThreadId
-threaded
, initial thread is boundWhoa... what happened? -threaded
30 times slower?
$ rm pingpong
$ ghc -threaded -O pingpong.hs
Linking pingpong ...
$ ./pingpong
...
mean: 113.6852 ms, lb 113.5195 ms, ub 113.8770 ms, ci 0.950
std dev: 912.0979 us, lb 731.0661 us, ub 1.226794 ms, ci 0.950
-threaded
, all Haskell threads run in one OS thread
-threaded
introduces multiple OS-level threads
unbound
haskell threads have same performance as w/o -threaded
forkIO
to make it unboundwrap :: IO a -> IO a
wrap action = do
mv <- newEmptyMVar
_ <- forkIO $ (action >>= putMVar mv) `catch`
\e@(SomeException _) -> putMVar mv (throw e)
takeMVar mv
runInUnboundThread
-threaded
, GHC ensures safe
FFI calls run in separate OS threadunsafe
FFI calls from unbound threads can block other threadspthread_getspecific
can get confused if called from a migrated unbound threadforkOn
Some handy MVar
utility functions for updating a value
modifyMVar :: MVar a -> (a -> IO (a, b)) -> IO b
modifyMVar_ :: MVar a -> (a -> IO a) -> IO ()
modifyMVar x (\n -> return (n+1, n))
" like "x++
" in CHow would you implement modifyMVar
?
modifyMVar :: MVar a -> (a -> IO (a,b)) -> IO b
modifyMVar m action = do
v0 <- takeMVar m
(v, r) <- action v0 `onException` putMVar m v0
putMVar m v
return r
throwTo
, killThread
)Some handy MVar
utility functions for updating a value
modifyMVar :: MVar a -> (a -> IO (a, b)) -> IO b
modifyMVar_ :: MVar a -> (a -> IO a) -> IO ()
modifyMVar x (\n -> return (n+1, n))
" like "x++
" in CHow would you implement modifyMVar
?
modifyMVar :: MVar a -> (a -> IO (a,b)) -> IO b
modifyMVar m action = do
v0 <- takeMVar m -- -------------- oops, race condition
(v, r) <- action v0 `onException` putMVar m v0
putMVar m v
return r
killThread
on the current thread while current thread between takeMVar
and onException
timeout
and wrap
functions from a few slides ago have same problemThe mask
function can sidestep such race conditions
mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b
RankNTypes
. For now, ignore "forall a.
"--just makes function more flexiblemask $ \f -> b
runs action b
with asynchronous exceptions maskedf
allows exceptions to be unmasked again for an actiontakeMVar
)Example: Fixing modifyMVar
modifyMVar :: MVar a -> (a -> IO (a,b)) -> IO b
modifyMVar m action = mask $ \unmask -> do
v0 <- takeMVar m -- automatically unmasked while waiting
(v, r) <- unmask (action v0) `onException` putMVar m v0
putMVar m v
return r
forkIO
preserves the current mask state
unmask
function in child threadwrap
functionwrap :: IO a -> IO a -- Fixed version of wrap
wrap action = do
mv <- newEmptyMVar
mask $ \unmask -> do
tid <- forkIO $ (unmask $ action >>= putMVar mv) `catch`
\e@(SomeException _) -> putMVar mv (throw e)
let loop = takeMVar mv `catch` \e@(SomeException _) ->
throwTo tid e >> loop
loop
unmask
in parent thread
loop
will sleep on takeMVar
, which implicitly unmasksbracket
functionmask
is tricky, but library function bracket
simplifies use
bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c
Example: process file without leaking handle
bracket (openFile "/etc/mtab" ReadMode) -- first
hClose -- last
(\h -> hGetContents h >>= doit) -- main
Example: fix parent
function from our timeout
example
parent = do ctid <- forkIO child -- old code,
result <- action -- bad if async
killThread ctid -- exception
return $ Just result
parent = bracket (forkIO child) killThread $ -- new code
\_ -> fmap Just action
MVar
sMVar
s work just fine as a mutex:
type Mutex = MVar ()
mutex_create :: IO Mutex
mutex_create = newMVar ()
mutex_lock, mutex_unlock :: Mutex -> IO ()
mutex_lock = takeMVar
mutex_unlock mv = putMVar mv ()
mutex_synchronize :: Mutex -> IO a -> IO a
mutex_synchronize mv action =
bracket (mutex_lock mv) (\_ -> mutex_unlock mv)
(\_ -> action)
Mutex
if it is locked
Mutex
Use full MVar
rather than empty to mean lock held
type Mutex = MVar ThreadId
mutex_create :: IO Mutex
mutex_create = newEmptyMVar
mutex_lock, mutex_unlock :: Mutex -> IO ()
mutex_lock mv = myThreadId >>= putMVar mv
mutex_unlock mv = do mytid <- myThreadId
lockTid <- tryTakeMVar mv
unless (lockTid == Just mytid) $
error "mutex_unlock"
ThreadId
of lock owner in MVar
mask
for this question...data Cond = Cond Mutex (MVar [MVar ()])
cond_create :: Mutex -> IO Cond
cond_create m = do
waiters <- newMVar []
return $ Cond m waiters
cond_wait, cond_signal, cond_broadcast :: Cond -> IO ()
cond_wait (Cond m waiters) = do
me <- newEmptyMVar
modifyMVar_ waiters $ \others -> return $ others ++ [me]
mutex_unlock m -- note we don't care if preempted here after this
takeMVar me `finally` mutex_lock m
cond_signal (Cond _ waiters) = modifyMVar_ waiters wakeone
where wakeone [] = return []
wakeone (w:ws) = putMVar w () >> return ws
cond_broadcast (Cond _ waiters) = modifyMVar_ waiters wakeall
where wakeall ws = mapM_ (flip putMVar ()) ws >> return []
MVar
s inside MVar
s is very powerfulControl.Concurrent.Chan
provides unbounded channels
MVar
s -- for read and and write end of Stream
data Item a = Item a (Stream a)
type Stream a = MVar (Item a)
data Chan a = Chan (MVar (Stream a)) (MVar (Stream a))
data Item a = Item a (Stream a)
type Stream a = MVar (Item a)
data Chan a = Chan (MVar (Stream a)) (MVar (Stream a))
newChan :: IO (Chan a)
newChan = do
empty <- newEmptyMVar
liftM2 Chan (newMVar empty) (newMVar empty)
writeChan :: Chan a -> a -> IO ()
writeChan (Chan _ w) a = do
empty <- newEmptyMVar
modifyMVar_ w $ \oldEmpty -> do
putMVar oldEmpty (Item a empty)
return empty
readChan :: Chan a -> IO a
readChan (Chan r _) =
modifyMVar r $ \full -> do
(Item a newFull) <- takeMVar full
return (newFull, a)
Network.Socket
socket :: Family -> SocketType -> ProtocolNumber -> IO Socket
connect :: Socket -> SockAddr -> IO ()
bindSocket :: Socket -> SockAddr -> IO ()
listen :: Socket -> Int -> IO ()
accept :: Socket -> IO (Socket, SockAddr)
getAddrInfo
looks up hostnames just like [RFC3493] (returns [
AddrInfo
]
)getAddrInfo :: Maybe AddrInfo
-> Maybe HostName -> Maybe ServiceName
-> IO [AddrInfo]
SockAddr
for talking to web server:webServerAddr :: String -> IO SockAddr
webServerAddr name = do
addrs <- getAddrInfo Nothing (Just name) (Just "www")
return $ addrAddress $ head $ addrs
netcat :: String -> String -> IO ()
netcat host port = do
-- Extract address from first AddrInfo in list
AddrInfo{addrAddress = addr}:_
<- getAddrInfo Nothing (Just host) (Just port)
-- Create a TCP socket connected to server
s <- socket AF_INET Stream 0
connect s addr
-- Convert socket to handle
h <- socketToHandle s ReadWriteMode
hSetBuffering h NoBuffering -- THIS IS IMPORTANT
-- Deal w. broken unicode
hSetBinaryMode stdout True
-- Copy data back and forth
done <- newEmptyMVar
forkIO $ (hGetContents h >>= putStr) `finally` putMVar done ()
getContents >>= hPutStr h
takeMVar done