Re: Staying alive

1999-10-06 Thread Sven Panne

Michael Weber wrote:
 [...] otherwise there would be a `marshalList' and `marshalListN' with
 same type signature, which I also regarded as confusing.

That was a problem with your approach, not mine...   :-)
 
 [...] But how else can you marshall an arbitrary length list? For
 Int lists, there is no zeroElem... [...]

A usual approach for this in many C-based APIs is that two arguments
are passed: a pointer and an integral of some kind, stating the number
of elements pointed to, see e.g. conformant arrays and the size_of
attribute in DCE-IDL (can't remember how MIDL calls this).

Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne



Re: Staying alive

1999-10-06 Thread Michael Weber

On Wed, Oct 06, 1999 at 12:04:03 +0200, Sven Panne wrote:
 Michael Weber wrote:
marshalListN :: Int - [a] - IO Addr
 
 I don't see a reason for the duplication of length information, e.g.
 what should `marshalListN 1000 [1,2,3]' mean? And
 `marshalListN 2 [1,2,3]' is equivalent to `marshalList (take 2 [1,2,3])'.

Yes... I thought about this, but otherwise there would be a `marshalList'
and `marshalListN' with same type signature, which I also regarded as
confusing.

 where `marshalList' stores the list length at the beginning of the buffer,
 like: [ marshalList code deleted ]

 This seems to be a rather special case, e.g. why should the length be
 marshaled as an Int? Some ancient Pascals on PCs used a byte length prefix
 for strings. And what about alignment? There could/must be some padding if
 the alignment constraints for the list element type are stronger than the
 ones for Int.

Yes, I know. I cursed on this stupid Pascal string limit in school :-) But
how else can you marshall an arbitrary length list? For Int lists, there is
no zeroElem...

BTW: This is what is done in XDR (eXternal Data Representation standard, see
RFC1832). The length is at the beginning, coded as big-endian 32Bit unsigned
int (we could use `writeInt32OffAddr . ccall_to_htonl' for this...)

 It seems that both spellings are possible and both "feel right", depending
 on the speaker and the dictionary.  :-)

That's what I expected... :-)


Cheers,
Michael



Re: Staying alive

1999-10-06 Thread Sven Panne

Michael Weber wrote:
 Maybe it's worth to know how many objects a list has (without explicit
 zeroElem), so I'd suggest to extend the class to:
 
marshalList   ::[a] - IO Addr

We agree here.

marshalListN  :: Int - [a] - IO Addr

I don't see a reason for the duplication of length information, e.g.
what should `marshalListN 1000 [1,2,3]' mean? And
`marshalListN 2 [1,2,3]' is equivalent to `marshalList (take 2 [1,2,3])'.

unmarshalList ::Addr - IO [a]

How many elements are there starting at the given Addr? Hmmm

unmarshalListN:: Int - Addr - IO [a]

This is my definition of unmarshalListN.

 where `marshalList' stores the list length at the beginning of the
 buffer, like:
 [ marshalList code deleted ]

This seems to be a rather special case, e.g. why should the length
be marshaled as an Int? Some ancient Pascals on PCs used a byte length
prefix for strings. And what about alignment? There could/must be some
padding if the alignment constraints for the list element type are
stronger than the ones for Int. Therefore this function does not belong
to a general purpose library IMHO.

I'll post a new proposal for a "better" Addr module later...

Cheers,
   Sven

P.S.: I've received a few personal mails regarding the spelling of
marshaling, but there is no real agreement on this. It seems that both
spellings are possible and both "feel right", depending on the speaker
and the dictionary.  :-)
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne



RFC: An extended Addr module

1999-10-06 Thread Sven Panne

GHC's Addr module is meant to be used in conjunction with the FFI (at
least this is what the docs told me :-), but its plethora of similar
functions is not very nice and some often needed functionality is
missing. Attached is my proposed new version of Addr, being very
similar to the things in the "Staying alive" thread. Some changes:

   * marshal.../unmarshal... are normal functions now and not methods
 of Marshalable anymore.

   * marshalList now returns the length of the list, too.

   * Some convenience functions for in/inout/out parameters are added.

   * After playing around with this module, I think that it is a
 Good Thing (tm) that ...OffAddr use element offsets and not byte
 offsets. It makes instance declarations of the following
 form much easier:

instance Marshalable a = Marshalable (Foo a) where ...

 Apart from that, it is much more consistent with the old
 definitions.

Alas, almost nobody mailed his/her wishes for a marshaling library, so
this proposal is obviously biased towards HOpenGL's (and I think
Manuel's) needs.

Comments/suggestions?

Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne

{- Hey Emacs, this is -*- haskell -*- !
   @configure_input@
This file was part of HOpenGL - a binding of OpenGL and GLUT for Haskell.
Copyright (C) 1999  Sven Panne [EMAIL PROTECTED]

This library is free software; you can redistribute it and/or
modify it under the terms of the GNU Library General Public
License as published by the Free Software Foundation; either
version 2 of the License, or (at your option) any later version.

This library is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
Library General Public License for more details.

You should have received a copy of the GNU Library General Public
License along with this library (COPYING.LIB); if not, write to the Free
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
-}

module Addr (
   Addr,
   nullAddr,  -- Addr
   plusAddr,  -- Addr - Int - Addr
   Marshalable(
  sizeOf, -- a - Int
  alignment,  -- a - Int
  indexOffAddr,   -- Addr - Int -a
  readOffAddr,-- Addr - Int - IO a
  writeOffAddr),  -- Addr - Int - a - IO ()
   marshal,   --  Marshalable a=   a  - IO Addr
   marshalList,   --  Marshalable a=  [a] - IO (Int, Addr),
   marshalListZero,   --  Marshalable a= a - [a] - IO Addr
   unmarshal, --  Marshalable a=Addr - IO  a
   unmarshalList, --  Marshalable a= Int - Addr - IO [a]
   unmarshalListZero, -- (Marshalable a, Eq a) = a   - Addr - IO [a]
   inParamWith,   -- (a - IO Addr) -   (Addr - IO b) - a - IO 
b
   inParam,   -- Marshalable a =(Addr - IO b) - a - IO 
b
   inOutParamWith,-- (a - IO Addr) - (Addr - IO a) - (Addr - IO b) - a - IO 
a
   inOutParam,-- Marshalable a =(Addr - IO b) - a - IO 
a
   outParamWith,  -- (a - Int) - (Addr - IO a) - (Addr - IO b)  - IO 
a
   outParam,  -- Marshalable a =(Addr - IO b)  - IO 
a
   malloc,-- Int  - IO Addr
   free   -- Addr - IO ()
) where

import Monad(when, zipWithM_)
import Addr
import Int
import Word

--
-- Haskell equivalent of raw pointers

{- We get these from Addr
data Addr = ...
instance Eq   Addr where ...
instance Ord  Addr where ...
instance Show Addr where ...

nullAddr :: Addr
plusAddr :: Addr - Int - Addr
-}

-- replacement for intToAddr/addrToInt
instance Enum Addr where
   toEnum   = intToAddr
   fromEnum = addrToInt

--
-- primitive marshaling

class Marshalable a where
   sizeOf   :: a - Int
   alignment:: a - Int
   -- replacement for index-/read-/write???OffAddr
   indexOffAddr :: Addr - Int -a
   readOffAddr  :: Addr - Int - IO a
   writeOffAddr :: Addr - Int - a - IO ()

-- system-dependent, but rather obvious instances
instance Marshalable Char where
   sizeOf   = const @SIZEOF_CHAR@
   alignment= const @ALIGNOF_CHAR@
   indexOffAddr = indexCharOffAddr
   readOffAddr  = readCharOffAddr
   writeOffAddr = writeCharOffAddr

instance Marshalable Int where
   sizeOf   = const @SIZEOF_INT@
   alignment= const @ALIGNOF_INT@
   indexOffAddr = indexIntOffAddr
   readOffAddr  = readIntOffAddr
   writeOffAddr = writeIntOffAddr

instance Marshalable Addr where