module Number where data Number -- fixed width integers instance Eq Number -- class instances instance Ord Number instance Show Number instance Enum Number instance Num Number instance Bounded Number instance Real Number instance Ix Number instance Integral Number
module IOExtensions where readBinaryFile :: FilePath -> IO String writeBinaryFile :: FilePath -> String -> IO () appendBinaryFile :: FilePath -> String -> IO () openBinaryFile :: FilePath -> IOMode -> IO Handle getCh :: IO Char fixIO :: (a -> IO a) -> IO a argv :: [String] garbageCollect :: IO () unsafePerformIO :: IO a -> a unsafeInterleaveIO :: IO a -> IO a
module ListUtils where deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] sums, products :: Num a => [a] -> [a] subsequences :: [a] -> [[a]] permutations :: [a] -> [[a]]
module Trace where trace :: String -> a -> aWhen called, trace prints the string in its first argument, and then returns the second argument as its result. The trace function is not referentially transparent, and should only be used for debugging, or for monitoring execution. You should also be warned that, unless you understand some of the details about the way that Hugs programs are executed, results obtained using trace can be rather confusing. For example, the messages may not appear in the order that you expect. Even ignoring the output that they produce, adding calls to trace can change the semantics of your program. Consider this a warning!
module Interact where type Interact = String -> String end :: Interact readChar, peekChar :: Interact -> (Char -> Interact) -> Interact pressAnyKey :: Interact -> Interact unreadChar :: Char -> Interact -> Interact writeChar :: Char -> Interact -> Interact writeStr :: String -> Interact -> Interact ringBell :: Interact -> Interact readLine :: String -> (String -> Interact) -> InteractAn expression e of type Interact can be executed as a program by evaluating run e.
module AnsiScreen where type Pos = (Int,Int) at :: Pos -> String -> String highlight :: String -> String goto :: Int -> Int -> String home :: String cls :: StringThe definitions in this module will need to be adapted to work with terminals that do not support ANSI escape sequences.
module AnsiInteract(module AnsiInteract,
module Interact,
module AnsiScreen) where
import AnsiScreen
import Interact
clearScreen :: Interact -> Interact
writeAt :: Pos -> String -> Interact -> Interact
moveTo :: Pos -> Interact -> Interact
readAt :: Pos -> -- start coords
Int -> -- max input length
(String -> Interact) -> -- continuation
Interact
defReadAt :: Pos -> -- start coords
Int -> -- max input length
String -> -- default value
(String -> Interact) -> -- continuation
Interact
promptReadAt :: Pos -> -- start coords
Int -> -- max input length
String -> -- prompt
(String -> Interact) -> -- continuation
Interact
defPromptReadAt :: Pos -> -- start coords
Int -> -- max input length
String -> -- prompt
String -> -- default value
(String -> Interact) -> -- continuation
Interact
module IORef where data Ref a -- Mutable reference cells, holding values of type a. newRef :: a -> IO (Ref a) getRef :: Ref a -> IO a setRef :: Ref a -> a -> IO () eqRef :: Ref a -> Ref a -> Bool instance Eq (Ref a)
module ST where
data MutVar s a -- mutable variables containing values
-- of type a in state thread s.
newVar :: a -> ST s (MutVar s a)
readVar :: MutVar s a -> ST s a
writeVar :: MutVar s a -> a -> ST s ()
interleaveST :: ST s a -> ST s a
instance Eq (MutVar s a)
instance Monad (ST s)
The runST operation, used to specify
encapsulation, is currently implemented as a language construct,
and runST is treated as a keyword.Note that it is possible to install Hugs 1.4 without support for lazy state threads, and hence the primitives described here may not be available in all implementations. Also, in contrast with the implementation of lazy state threads in previous releases of Hugs and Gofer, there is no direct relationship between the ST and the IO monads.
module STArray where
data MutArr s a b -- Mutable arrays, indexed by type a, with
-- results of type b in state thread s.
newArr :: Ix a => (a,a) -> b -> ST s (MutArr s a b)
readArr :: Ix a => MutArr s a b -> a -> ST s b
writeArr :: Ix a => MutArr s a b -> a -> b -> ST s ()
freezeArr :: Ix a => MutArr s a b -> ST s (Array a b)
There is one significant difference between the implementation of these features in GHC and in Hugs:
main = forkIO (write 'a') >> write 'b'
where write c = putChar c >> write c
will print either aaaaaaaaaaaaaa... or bbbbbbbbbbbb...,
instead of some random interleaving of as and bs.
module MVar where data MVar a -- datatype of MVars forkIO :: IO a -> IO () -- Spawn a thread newMVar :: IO (MVar a) takeMVar :: MVar a -> IO a putMVar :: MVar a -> a -> IO () instance Eq (MVar a)
module Channel where data Channel a -- datatype of buffered channels newChan :: IO (Channel a) putChan :: Channel a -> a -> IO () getChan :: Channel a -> IO a dupChan :: Channel a -> IO (Channel a)
module CVar where
import MVar
type CVar a = (MVar a, -- Producer -> consumer
MVar ()) -- Consumer -> producer
newCVar :: IO (CVar a)
putCVar :: CVar a -> a -> IO ()
getCVar :: CVar a -> IO a