diff --git a/ghc/docs/libraries/Addr.sgml b/ghc/docs/libraries/Addr.sgml index 8681ee02e52877cc7101a2df3a80a12fb2dc9c18..39c62da81f8fce50b2458d69194cec8307d4f720 100644 --- a/ghc/docs/libraries/Addr.sgml +++ b/ghc/docs/libraries/Addr.sgml @@ -9,13 +9,14 @@ use in creating foreign function interfaces using GreenCard. module Addr where data Addr -- Address type instance Eq Addr +instance Ord Addr nullAddr :: Addr plusAddr :: Addr -> Int -> Addr -- read value out of _immutable_ memory indexCharOffAddr :: Addr -> Int -> Char -indexIntOffAddr :: Addr -> Int -> Int -- should we drop this? +indexIntOffAddr :: Addr -> Int -> Int indexAddrOffAddr :: Addr -> Int -> Addr indexFloatOffAddr :: Addr -> Int -> Float indexDoubleOffAddr :: Addr -> Int -> Double @@ -30,7 +31,7 @@ indexInt64OffAddr :: Addr -> Int -> Int64 -- read value out of mutable memory readCharOffAddr :: Addr -> Int -> IO Char -readIntOffAddr :: Addr -> Int -> IO Int -- should we drop this? +readIntOffAddr :: Addr -> Int -> IO Int readAddrOffAddr :: Addr -> Int -> IO Addr readFloatOffAddr :: Addr -> Int -> IO Float readDoubleOffAddr :: Addr -> Int -> IO Double @@ -45,7 +46,7 @@ readInt64OffAddr :: Addr -> Int -> IO Int64 -- write value into mutable memory writeCharOffAddr :: Addr -> Int -> Char -> IO () -writeIntOffAddr :: Addr -> Int -> Int -> IO () -- should we drop this? +writeIntOffAddr :: Addr -> Int -> Int -> IO () writeAddrOffAddr :: Addr -> Int -> Addr -> IO () writeForeignObjOffAddr :: Addr -> Int -> ForeignObj -> IO () writeFloatOffAddr :: Addr -> Int -> Float -> IO () diff --git a/ghc/docs/libraries/Concurrent.sgml b/ghc/docs/libraries/Concurrent.sgml index 1ea694871d774059b79fde88ed40cac18d4f6742..4af56157172ec5bf3d3d76828744fdc2cb76faf4 100644 --- a/ghc/docs/libraries/Concurrent.sgml +++ b/ghc/docs/libraries/Concurrent.sgml @@ -108,7 +108,7 @@ will a thread block when performing a <tt/takeMVar/ on that Please notice that the Boolean value returned from <tt/isEmptyMVar/ represent just a snapshot of the state of the <tt/MVar/. By the time a thread gets to inspect the result and act upon it, other -threads may have accessed the <tt/MVar/ and changed its 'filled-in' -status of the variable. Please be wary of this. +threads may have accessed the <tt/MVar/ and changed the 'filled-in' +status of the variable. </itemize> diff --git a/ghc/docs/libraries/Dynamic.sgml b/ghc/docs/libraries/Dynamic.sgml index a137b2d965ca1128009b5041dda1422e4676896a..eccaddb285de9ddb273ca053efaf976f42ecaa53 100644 --- a/ghc/docs/libraries/Dynamic.sgml +++ b/ghc/docs/libraries/Dynamic.sgml @@ -8,13 +8,14 @@ information with it at run-time, and is represented here by the abstract type <tt/Dynamic/. Values can be converted into <tt/Dynamic/ ones, which can then be combined and manipulated by the program using the operations provided over the abstract, dynamic type. One of -these operations allows you to convert a dynamically-typed value back -into a value with the same (monomorphic) type it had before converting -it into a dynamically-typed value. +these operations allows you to (try to) convert a dynamically-typed +value back into a value with the same (monomorphic) type it had before +converting it into a dynamically-typed value. If the dynamically-typed +value isn't of the desired type, the coercion will fail. The <tt/Dynamic/ library is capable of dealing with monomorphic types only; no support for polymorphic dynamic values, but hopefully that -can be added at a later stage. +will be added at a later stage. Examples where this library may come in handy (dynamic types, really - hopefully the library provided here will suffice) are: persistent @@ -109,7 +110,7 @@ i.e., (<tt/mkTyCon ",,,,"/), is shown as an <tt/(n+1)/ tuple in infix form. </itemize> -<sect1>The <tt/Typeable/ class +<sect1><idx>The Typeable class</idx> <nidx>Typeable class</nidx> <label id="sec:Dynamic:Typeable"> <p> diff --git a/ghc/docs/libraries/Foreign.sgml b/ghc/docs/libraries/Foreign.sgml new file mode 100644 index 0000000000000000000000000000000000000000..4f59f39beeaa9bce176f3e3a787426e8ea0a96c3 --- /dev/null +++ b/ghc/docs/libraries/Foreign.sgml @@ -0,0 +1,95 @@ + <sect> <idx/Foreign/ +<label id="sec:Foreign"> +<p> + +This module provides two types to better allow the Haskell world to +share its data with the outside world (and vice versa), <em/foreign +objects/ and <em/stable pointers/: + +<tscreen><verb> +module Foreign where +data ForeignObj -- abstract, instance of: Eq + +makeForeignObj :: Addr{-object-} -> Addr{-finaliser-} -> IO ForeignObj +writeForeignObj :: ForeignObj -> Addr{-new value-} -> IO () + +data StablePtr a -- abstract, instance of: Eq. +makeStablePtr :: a -> IO (StablePtr a) +deRefStablePtr :: StablePtr a -> IO a +freeStablePtr :: StablePtr a -> IO () +</verb> </tscreen> + +<itemize> +<item>The <tt/ForeignObj/ type provides foreign objects, encapsulated +references to values outside the Haskell heap. Foreign objects are +finalised by the garbage collector when they become dead. The +finaliser to use is given as second argument to <tt/makeForeignOj/, +and is currently a function pointer to a C function with +the following signature + +<tscreen><verb> +void finaliseFO(void* obj); +</verb></tscreen> + +The finaliser is passed the reference to the external object (i.e., +the first argument to <tt/makeForeignObj/.) + +<item> +The <tt/writeForeignObj/ lets you overwrite the encapsulated foreign +reference with another. + +<item> +Stable pointers allow you to hand out references to Haskell heap +objects to the outside world. <bf/ToDo:/ <em/say more./ +</itemize> + +In addition to the above, the following operations for indexing via +a <tt/ForeignObj/ are also, mirrored on the same operations provided +over <tt/Addr/s: + +<tscreen><verb> +indexCharOffForeignObj :: ForeignObj -> Int -> Char +indexIntOffForeignObj :: ForeignObj -> Int -> Int +indexAddrOffForeignObj :: ForeignObj -> Int -> Addr +indexFloatOffForeignObj :: ForeignObj -> Int -> Float +indexDoubleOffForeignObj :: ForeignObj -> Int -> Double +indexWord8OffForeignObj :: ForeignObj -> Int -> Word8 +indexWord16OffForeignObj :: ForeignObj -> Int -> Word16 +indexWord32OffForeignObj :: ForeignObj -> Int -> Word32 +indexWord64OffForeignObj :: ForeignObj -> Int -> Word64 + +indexInt8OffForeignObj :: ForeignObj -> Int -> Int8 +indexInt16OffForeignObj :: ForeignObj -> Int -> Int16 +indexInt32OffForeignObj :: ForeignObj -> Int -> Int32 +indexInt64OffForeignObj :: ForeignObj -> Int -> Int64 + +-- read value out of mutable memory +readCharOffForeignObj :: ForeignObj -> Int -> IO Char +readIntOffForeignObj :: ForeignObj -> Int -> IO Int +readAddrOffForeignObj :: ForeignObj -> Int -> IO Addr +readFloatOffForeignObj :: ForeignObj -> Int -> IO Float +readDoubleOffForeignObj :: ForeignObj -> Int -> IO Double +readWord8OffForeignObj :: ForeignObj -> Int -> IO Word8 +readWord16OffForeignObj :: ForeignObj -> Int -> IO Word16 +readWord32OffForeignObj :: ForeignObj -> Int -> IO Word32 +readWord64OffForeignObj :: ForeignObj -> Int -> IO Word64 +readInt8OffForeignObj :: ForeignObj -> Int -> IO Int8 +readInt16OffForeignObj :: ForeignObj -> Int -> IO Int16 +readInt32OffForeignObj :: ForeignObj -> Int -> IO Int32 +readInt64OffForeignObj :: ForeignObj -> Int -> IO Int64 + +writeCharOffForeignObj :: ForeignObj -> Int -> Char -> IO () +writeIntOffForeignObj :: ForeignObj -> Int -> Int -> IO () +writeAddrOffForeignObj :: ForeignObj -> Int -> Addr -> IO () +writeFloatOffForeignObj :: ForeignObj -> Int -> Float -> IO () +writeDoubleOffForeignObj :: ForeignObj -> Int -> Double -> IO () +writeWord8OffForeignObj :: ForeignObj -> Int -> Word8 -> IO () +writeWord16OffForeignObj :: ForeignObj -> Int -> Word16 -> IO () +writeWord32OffForeignObj :: ForeignObj -> Int -> Word32 -> IO () +writeWord64OffForeignObj :: ForeignObj -> Int -> Word64 -> IO () +writeInt8OffForeignObj :: ForeignObj -> Int -> Int8 -> IO () +writeInt16OffForeignObj :: ForeignObj -> Int -> Int16 -> IO () +writeInt32OffForeignObj :: ForeignObj -> Int -> Int32 -> IO () +writeInt64OffForeignObj :: ForeignObj -> Int -> Int64 -> IO () +</verb></tscreen> + diff --git a/ghc/docs/libraries/IOExts.sgml b/ghc/docs/libraries/IOExts.sgml index faa0a23a69406dc8087ae70e226669cc9696e997..b2d1ddd97c755ccc92d8035110165790b9451897 100644 --- a/ghc/docs/libraries/IOExts.sgml +++ b/ghc/docs/libraries/IOExts.sgml @@ -20,10 +20,12 @@ for opening binary files. <tt/performGC/ triggers an immediate garbage collection <item> -When called, <tt/trace/ prints the string in its first argument, and then -returns the second argument as its result. The <tt/trace/ function is not -referentially transparent, and should only be used for debugging, or for -monitoring execution. +When called, <tt/trace/ prints the string in its first argument to +standard error, before returning the second argument as its result. +The <tt/trace/ function is not referentially transparent, and should +only be used for debugging, or for monitoring execution. Some +implementations of <tt/trace/ may decorate the string that's output +to indicate that you're tracing. <!-- You should also be warned that, unless you understand some of the @@ -58,7 +60,7 @@ simplified memoisation function: <item> Operations for coercing an <tt/ST/ action into an <tt/IO/ one, and -vice versa are also provided. Notice that coercing an <tt/IO action +vice versa are also provided. Notice that coercing an <tt/IO/ action into an <tt/ST/ action is 'lossy', since any exception raised within the <tt/IO/ action will not be caught within the <tt/ST/ monad, as it doesn't support (monadic) exceptions. diff --git a/ghc/docs/libraries/Int.sgml b/ghc/docs/libraries/Int.sgml index 13c9e55858263877dee08f6984b674d9aa3dfe3e..a36c667e7dfc5519a45db995cf9b31fc35c92139 100644 --- a/ghc/docs/libraries/Int.sgml +++ b/ghc/docs/libraries/Int.sgml @@ -20,7 +20,7 @@ For each type <it/I/ above, we provide the following instances. <tscreen><verb> data I -- Signed Ints iToInt :: I -> Int -- not provided for Int64 -intToi :: Int -> I -- not provided for Int64 +intToI :: Int -> I -- not provided for Int64 instance Eq I instance Ord I instance Show I diff --git a/ghc/docs/libraries/NumExts.sgml b/ghc/docs/libraries/NumExts.sgml index ee372dfaee08d52e09eadce67914df44c2752aac..ca34f1cf8e98cfd1a81b56e6418f5802644cdac8 100644 --- a/ghc/docs/libraries/NumExts.sgml +++ b/ghc/docs/libraries/NumExts.sgml @@ -12,6 +12,13 @@ floatToDouble :: Float -> Double showHex :: Integral a => a -> ShowS showOct :: Integral a => a -> ShowS +showBin :: Integral a => a -> ShowS + +showIntAtBase :: Integral a + => a -- base + -> (a -> Char) -- digit to char + -> a -- number to show. + -> ShowS </verb> </tscreen> Notes: @@ -25,7 +32,24 @@ Notes: No loss of precision occurs in the other direction with <tt/floatToDouble/, the floating value remains unchanged. <item> - <tt/showOct/ and <tt/showHex/ will prefix <tt/0o/ and <tt/0x/ - respectively. Like <tt/Numeric.showInt/, these show functions - work on positive numbers only. + <tt/showOct/, <tt/showHex/ and <tt/showBin/ will prefix <tt/0o/, + <tt/0x/ and <tt/0b/, respectively. Like <tt/Numeric.showInt/, + these show functions work on positive numbers only. +<item> + <tt/showIntAtBase/ is the more general function for converting + a number at some base into a series of characters. The above + <tt/show*/ functions use it, for instance, here's how <tt/showHex/ + could be defined + +<tscreen><verb> + +</verb></tscreen> +showHex :: Integral a => a -> ShowS +showHex n r = + showString "0x" $ + showIntAtBase 16 (toChrHex) n r + where + toChrHex d + | d < 10 = chr (ord '0' + fromIntegral d) + | otherwise = chr (ord 'a' + fromIntegral (d - 10)) </itemize> diff --git a/ghc/docs/libraries/Word.sgml b/ghc/docs/libraries/Word.sgml index 843bdb1d9927f78993325fce072b3204a40a9d06..eb82c2ae4f5e105277cbb5aaa2aca43569271983 100644 --- a/ghc/docs/libraries/Word.sgml +++ b/ghc/docs/libraries/Word.sgml @@ -53,7 +53,7 @@ Notes: <item> All arithmetic is performed modulo 2^n - One non-obvious consequequence of this is that <tt/negate/ + One non-obvious consequence of this is that <tt/negate/ should <em/not/ raise an error on negative arguments. <item> diff --git a/ghc/docs/libraries/libs.sgml b/ghc/docs/libraries/libs.sgml index ab6e04feadfd7901705b9711e3f0f34debb201fd..29175f1cd3bd8160bd51ba336b3325717d968749 100644 --- a/ghc/docs/libraries/libs.sgml +++ b/ghc/docs/libraries/libs.sgml @@ -4,6 +4,7 @@ <!ENTITY concurrent SYSTEM "Concurrent.sgml"> <!ENTITY dynamic SYSTEM "Dynamic.sgml"> <!ENTITY exception SYSTEM "Exception.sgml"> + <!ENTITY foreign SYSTEM "Foreign.sgml"> <!ENTITY glaexts SYSTEM "GlaExts.sgml"> <!ENTITY ioexts SYSTEM "IOExts.sgml"> <!ENTITY int SYSTEM "Int.sgml"> @@ -23,14 +24,12 @@ <article> <title>The Hugs-GHC Extension Libraries -<author>Alastair Reid <tt/reid-alastair@cs.yale.edu/ - Simon Marlow <tt/simonm@dcs.gla.ac.uk/ -<date>v0.8, 28 January 1998 +<author>The Hugs/GHC Team +<date>January 1999 <abstract> Hugs and GHC provide a common set of libraries to aid portability. This document specifies the interfaces to these libraries and documents -known differences. We hope that these modules will be adopted for inclusion -as Standard Haskell Libraries sometime soon. +known differences. </abstract> <toc> @@ -82,17 +81,15 @@ the form <tt/getXContents/, e.g., <tt/Channel.getChanContents/ and &concurrent &dynamic &exception - -<sect> <idx/Foreign/ -<label id="sec:Foreign"> -<p> -This module is provided by GHC but not by Hugs. -GreenCard for Hugs provides the <tt/ForeignObj/ type. - +&foreign &glaexts &ioexts &int +&numexts +&pretty +&st + <sect> <idx/LazyST/ <label id="sec:LazyST"> <p> @@ -113,9 +110,6 @@ semantics with respect to laziness are as you would expect: the strict state thread passed to <tt/strictToLazyST/ is not performed until the result of the lazy state thread it returns is demanded. -&numexts -&pretty -&st &weak &word