Array operations and pinning

Rene de Visser rene_de_visser at hotmail.com
Wed Nov 2 06:15:03 EST 2005


Hello,

Where is the documentation on how pinning works in the GHC garbage collector 
(from a GHC users point of view).

I have copied the following code from array/IO.hs and am thinking that it is 
assuming that the array is pinned? What triggers the pinning?

On a second note.
Why is the type signiture so constricted. The code below works on any 
IOUArray (which is very usefull, not just on Int Word8). Naturally this 
assumes the particular in memory array layout that GHC uses on a particular 
platform, so would not be compatible (probably) with other Haskell 
compilers.

Rene.

hPutArray
	:: Handle			-- ^ Handle to write to
	-> IOUArray Int Word8		-- ^ Array to write from
	-> Int				-- ^ Number of 'Word8's to write
	-> IO ()

hPutArray handle (IOUArray (STUArray l u raw)) count
  | count == 0
  = return ()
  | count < 0 || count > rangeSize (l,u)
  = illegalBufferSize handle "hPutArray" count
  | otherwise
   = do wantWritableHandle "hPutArray" handle $
          \ handle_ at Handle__{ haFD=fd, haBuffer=ref, haIsStream=stream } -> 
do

          old_buf at Buffer{ bufBuf=old_raw, bufRPtr=r, bufWPtr=w, bufSize=size 
}
	    <- readIORef ref

          -- enough room in handle buffer?
          if (size - w > count)
		-- There's enough room in the buffer:
		-- just copy the data in and update bufWPtr.
	    then do memcpy_baoff_ba old_raw w raw (fromIntegral count)
		    writeIORef ref old_buf{ bufWPtr = w + count }
		    return ()

		-- else, we have to flush
	    else do flushed_buf <- flushWriteBuffer fd stream old_buf
		    writeIORef ref flushed_buf
		    let this_buf =
			    Buffer{ bufBuf=raw, bufState=WriteBuffer,
				    bufRPtr=0, bufWPtr=count, bufSize=count }
		    flushWriteBuffer fd stream this_buf
		    return ()




More information about the Glasgow-haskell-users mailing list