Re: [Haskell-cafe] carry state around ....

2008-07-29 Thread Ketil Malde
Galchin, Vasili [EMAIL PROTECTED] writes:

 ok guys .. what is this phantom type concept? Is it a type theory thing or
 just Haskell type concept?

Here's another example.  Say you want to use bytestrings with
different encodings.  You obviously don't want to concatenate a string
representing Latin characters with a string in Cyrillic.

One way to do this, is to define phantom types for the encodings, and
a bytestring type that takes additional type parameter

   data KOI8
   data ISO8859_1
 :

   data Bytestring enc = MkBS ...

Operations like concat work on same-typed bytestrings:

   concat :: Bytestring e - Bytestring e - Bytestring e

The parameter (enc) isn't used on the right hand side, so all
Bytestrings will have the same representation, but Bytestring KOI8 and
Bytestring ISO8859_1 will have different types, so although the
runtime won't know the difference, trying to 'concat' them will give
you a type error at compile time. 

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-28 Thread Brandon S. Allbery KF8NH


On 2008 Jul 28, at 1:54, Galchin, Vasili wrote:


   allocaBytes (#const sizeof(struct aiocb)) $ \ p_aiocb - do
  poke p_aiocb aiocb


As I understand it, you can't do this;you must use the same aiocb  
throughout (that is, the same chunk of memory, not merely the same  
values; there is quite possibly a kernel mapping to it which you can't  
change or copy, or a pointer to the original aiocb is kept as internal  
state in the aio library so it can update the errno and result on the  
fly).


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-28 Thread Galchin, Vasili
Hi Brandon,

  So even if I go to ForeignPtr is a problem? And/Or is this a by
reference vs by value issue?

Kind regards, Vasili

On Mon, Jul 28, 2008 at 1:09 AM, Brandon S. Allbery KF8NH 
[EMAIL PROTECTED] wrote:


 On 2008 Jul 28, at 1:54, Galchin, Vasili wrote:

allocaBytes (#const sizeof(struct aiocb)) $ \ p_aiocb - do
   poke p_aiocb aiocb


 As I understand it, you can't do this;you must use the same aiocb
 throughout (that is, the same chunk of memory, not merely the same values;
 there is quite possibly a kernel mapping to it which you can't change or
 copy, or a pointer to the original aiocb is kept as internal state in the
 aio library so it can update the errno and result on the fly).

 --
 brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
 system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
 electrical and computer engineering, carnegie mellon universityKF8NH



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-28 Thread Galchin, Vasili
Hi Brandon,

 So based on what you are saying I kind of need a Haskell AIO
imperative/monadic function that basically returns a handle that is
associated with this AIOCB chunk-of-memory  This handle gets passed
around during an AIO I/O session?? Sorry for talking too imperatively ;^)
 smiley face ;^)

Vasili

On Mon, Jul 28, 2008 at 1:09 AM, Brandon S. Allbery KF8NH 
[EMAIL PROTECTED] wrote:


 On 2008 Jul 28, at 1:54, Galchin, Vasili wrote:

allocaBytes (#const sizeof(struct aiocb)) $ \ p_aiocb - do
   poke p_aiocb aiocb


 As I understand it, you can't do this;you must use the same aiocb
 throughout (that is, the same chunk of memory, not merely the same values;
 there is quite possibly a kernel mapping to it which you can't change or
 copy, or a pointer to the original aiocb is kept as internal state in the
 aio library so it can update the errno and result on the fly).

 --
 brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
 system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
 electrical and computer engineering, carnegie mellon universityKF8NH



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-28 Thread Brandon S. Allbery KF8NH


On 2008 Jul 28, at 2:36, Galchin, Vasili wrote:


Hi Brandon,

  So even if I go to ForeignPtr is a problem? And/Or is this a  
by reference vs by value issue?



As I read your code, you're allocating a C object, poking the Haskell  
fields into it, and passing it on, then peeking the values back out.   
This won't work; the C pointer value passed to aio_write() is the  
value that must be passed to subsequent operations on that aiocb (such  
as aio_return()).  More to the point:  the exact chunk of memory  
passed to aio_write(), unmodified, must be passed to any other aio  
functions checking for or blocking on completion of the write.  You  
may not move it around or arbitrarily change values within it.


You could do this if your Haskell aiocb also retained the ForeignPtr  
to the originally allocated C object... but after the initial pokes,  
the only thing you can safely do with that object is pass it to C and  
peek the current values out of it, unless the C API specifically says  
you can modify fields within it while I/O operations are pending (and  
I'd be rather surprised if it did).


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-28 Thread Brandon S. Allbery KF8NH


On 2008 Jul 28, at 2:41, Galchin, Vasili wrote:

 So based on what you are saying I kind of need a Haskell AIO  
imperative/monadic function that basically returns a handle that  
is associated with this AIOCB chunk-of-memory  This handle gets  
passed around during an AIO I/O session?? Sorry for talking too  
imperatively ;^)  smiley face ;^)


I/O *is* monadic in Haskell, so you're kinda there anyway.  I would in  
fact use a custom state (AIO = StateT ForeignPtr IO) if I were doing  
it; I would hide the constructor so that the only way to alter values  
is to call specific function(s) returning filled-in aiocbs as  
initialized and passed to aio_read/aio_write, then provide accessors  
for the contents (which if necessary can call aio_return, aio_suspend,  
or aio_error).  Returning from the monad would invoke aio_suspend to  
wait for completion or aio_cancel to abort.  (Hm.  Could be argued  
that we want ContT here to represent the two possibilities.)


I note from my local documentation that (a) indeed you must not modify  
the aiocb after passing it to aio_read/aio_write and (b) the offset  
value should not be read, much less modified, because it could change  
during the async I/O (and not in a reliably useful fashion; consider  
buffering).  And as I said earlier, the exact same memory block (not  
merely a copy of it) must be used for the same aiocb.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-28 Thread Galchin, Vasili
Brandon,

 Your reading on my code is quite correct. So you are suggesting that
the Haskell aiocb contain a ForeignPtr to actual aiocb that is passed the C
functions. In this scenario, whose responsibility to allocate the chunk of
memory for the  aiocb?

Vasili

On Mon, Jul 28, 2008 at 2:04 AM, Brandon S. Allbery KF8NH 
[EMAIL PROTECTED] wrote:


 On 2008 Jul 28, at 2:36, Galchin, Vasili wrote:

 Hi Brandon,

   So even if I go to ForeignPtr is a problem? And/Or is this a by
 reference vs by value issue?


 As I read your code, you're allocating a C object, poking the Haskell
 fields into it, and passing it on, then peeking the values back out.  This
 won't work; the C pointer value passed to aio_write() is the value that must
 be passed to subsequent operations on that aiocb (such as aio_return()).
  More to the point:  the exact chunk of memory passed to aio_write(),
 unmodified, must be passed to any other aio functions checking for or
 blocking on completion of the write.  You may not move it around or
 arbitrarily change values within it.

 You could do this if your Haskell aiocb also retained the ForeignPtr to the
 originally allocated C object... but after the initial pokes, the only thing
 you can safely do with that object is pass it to C and peek the current
 values out of it, unless the C API specifically says you can modify fields
 within it while I/O operations are pending (and I'd be rather surprised if
 it did).

 --
 brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
 system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
 electrical and computer engineering, carnegie mellon universityKF8NH



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-28 Thread Galchin, Vasili
 So at the moment you're using using Storable and a Haskell record, say:

 data AIOCB = AIOCB {
...
  }

 and we're suggesting instead:

 newtype AIOCB = AIOCB (ForeignPtr AIOCB)


  ^^^ I am somewhat new to Haskell. Not a total newbie! But what exactly
does the above mean? Are the three references of AIOCB in different
namespaces? If it too much trouble to explain, can you point me at Haskell
URL to read?




 then to access a member use hsc2hs:

 getBlah :: AIOCB - IO Blah
 getBlah (AIOCB fptr) =
  withForeignPtr fptr $ \ptr - {# peek aiocb,blah #} ptr

 So you only access the parts you need and keep the aiocb C struct
 allocated on the heap (use mallocForeignPtr).

 Duncan


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-28 Thread Felipe Lessa
2008/7/28 Galchin, Vasili [EMAIL PROTECTED]:
 and we're suggesting instead:

 newtype AIOCB = AIOCB (ForeignPtr AIOCB)

   ^^^ I am somewhat new to Haskell. Not a total newbie! But what exactly
 does the above mean? Are the three references of AIOCB in different
 namespaces?

The first and the third are the type AIOCB, the second is the type
constructor AIOCB. That is, it is equivalent (up to renaming) to

newtype T = C (ForeignPtr T)

Now, why use Type in Type's definition? It is obvious that if we were creating

data T = D T

it would be pretty useless, however the type that ForeignPtr requires
is just a phantom type. In other words, the ForeignPtr will never use
the C constructor.

An analogy to C: if you have

typeA *pa;
typeB *pb;

then of course pa and pb have different types, however their internal
representation are the same: an integral type of 32/64 bits. The C
compiler only uses the type to provide warnings, to know the fields'
offsets, the size of the structure, etc. The same goes for Haskell, if
you have

pa :: ForeignPtr A
pb :: ForeignPtr B

then both pa and pb have different types, but again they have the same
internal representation. However, for example, if you allocate memory
for pa via Storable then the compiler will find the correct sizeOf
definition because will gave the type hint. The compiler also won't
you let mix pa and pb like in [pa,pb].



So, if you declare

newtype T = C (ForeignPtr T)

you are:

1) Hiding the ForeignPtr from the users of your library if you don't export C.
2) Having type safeness by using ForeignPtr T instead of something
generic like ForeignPtr () -- the same as using typeA* instead of
void*.
3) Not needing to create a different type, like

data InternalT = InternalT
newtype T = C (ForeignPtr InternalT)


Well.. did it help at all? =)

-- 
Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-28 Thread Galchin, Vasili
Thanks, Felipe.



On Mon, Jul 28, 2008 at 8:01 PM, Felipe Lessa [EMAIL PROTECTED]wrote:

 2008/7/28 Galchin, Vasili [EMAIL PROTECTED]:
  and we're suggesting instead:
 
  newtype AIOCB = AIOCB (ForeignPtr AIOCB)
 
^^^ I am somewhat new to Haskell. Not a total newbie! But what
 exactly
  does the above mean? Are the three references of AIOCB in different
  namespaces?

 The first and the third are the type AIOCB, the second is the type
 constructor AIOCB. That is, it is equivalent (up to renaming) to

 newtype T = C (ForeignPtr T)

 Now, why use Type in Type's definition? It is obvious that if we were
 creating

 data T = D T

 it would be pretty useless, however the type that ForeignPtr requires
 is just a phantom type. In other words, the ForeignPtr will never use
 the C constructor.

 An analogy to C: if you have

 typeA *pa;
 typeB *pb;

 then of course pa and pb have different types, however their internal
 representation are the same: an integral type of 32/64 bits. The C
 compiler only uses the type to provide warnings, to know the fields'
 offsets, the size of the structure, etc. The same goes for Haskell, if
 you have

 pa :: ForeignPtr A
 pb :: ForeignPtr B

 then both pa and pb have different types, but again they have the same
 internal representation. However, for example, if you allocate memory
 for pa via Storable then the compiler will find the correct sizeOf
 definition because will gave the type hint. The compiler also won't
 you let mix pa and pb like in [pa,pb].



 So, if you declare

 newtype T = C (ForeignPtr T)

 you are:

 1) Hiding the ForeignPtr from the users of your library if you don't export
 C.
 2) Having type safeness by using ForeignPtr T instead of something
 generic like ForeignPtr () -- the same as using typeA* instead of
 void*.
 3) Not needing to create a different type, like

 data InternalT = InternalT
 newtype T = C (ForeignPtr InternalT)


 Well.. did it help at all? =)

 --
 Felipe.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-28 Thread Galchin, Vasili
what does a datatype with no constructors mean?

E.g.

data RSAStruct
data EVP_PKEY
data EVP_CIPHER
data EVP_CIPHER_CTX
data EVP_MD_CTX
data EVP_MD
data BIGNUM



On Mon, Jul 28, 2008 at 8:01 PM, Felipe Lessa [EMAIL PROTECTED]wrote:

 2008/7/28 Galchin, Vasili [EMAIL PROTECTED]:
  and we're suggesting instead:
 
  newtype AIOCB = AIOCB (ForeignPtr AIOCB)
 
^^^ I am somewhat new to Haskell. Not a total newbie! But what
 exactly
  does the above mean? Are the three references of AIOCB in different
  namespaces?

 The first and the third are the type AIOCB, the second is the type
 constructor AIOCB. That is, it is equivalent (up to renaming) to

 newtype T = C (ForeignPtr T)

 Now, why use Type in Type's definition? It is obvious that if we were
 creating

 data T = D T

 it would be pretty useless, however the type that ForeignPtr requires
 is just a phantom type. In other words, the ForeignPtr will never use
 the C constructor.

 An analogy to C: if you have

 typeA *pa;
 typeB *pb;

 then of course pa and pb have different types, however their internal
 representation are the same: an integral type of 32/64 bits. The C
 compiler only uses the type to provide warnings, to know the fields'
 offsets, the size of the structure, etc. The same goes for Haskell, if
 you have

 pa :: ForeignPtr A
 pb :: ForeignPtr B

 then both pa and pb have different types, but again they have the same
 internal representation. However, for example, if you allocate memory
 for pa via Storable then the compiler will find the correct sizeOf
 definition because will gave the type hint. The compiler also won't
 you let mix pa and pb like in [pa,pb].



 So, if you declare

 newtype T = C (ForeignPtr T)

 you are:

 1) Hiding the ForeignPtr from the users of your library if you don't export
 C.
 2) Having type safeness by using ForeignPtr T instead of something
 generic like ForeignPtr () -- the same as using typeA* instead of
 void*.
 3) Not needing to create a different type, like

 data InternalT = InternalT
 newtype T = C (ForeignPtr InternalT)


 Well.. did it help at all? =)

 --
 Felipe.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-28 Thread Bryan Donlan
On Mon, Jul 28, 2008 at 08:48:23PM -0500, Galchin, Vasili wrote:
 what does a datatype with no constructors mean?
 
 E.g.
 
 data RSAStruct
 data EVP_PKEY
 data EVP_CIPHER
 data EVP_CIPHER_CTX
 data EVP_MD_CTX
 data EVP_MD
 data BIGNUM

It's simply a datatype that can never have a value - a so-called
'phantom type'. They're useful when you need a type (eg as the argument
for a ForeignPointer) but no need for an actual value.

You can of course create values of these types using 'undefined',
'error' and friends, but this is perhaps not very useful most of the
time :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-28 Thread Galchin, Vasili
ok guys .. what is this phantom type concept? Is it a type theory thing or
just Haskell type concept?

Vasili

On Mon, Jul 28, 2008 at 8:53 PM, Bryan Donlan [EMAIL PROTECTED] wrote:

 On Mon, Jul 28, 2008 at 08:48:23PM -0500, Galchin, Vasili wrote:
  what does a datatype with no constructors mean?
 
  E.g.
 
  data RSAStruct
  data EVP_PKEY
  data EVP_CIPHER
  data EVP_CIPHER_CTX
  data EVP_MD_CTX
  data EVP_MD
  data BIGNUM

 It's simply a datatype that can never have a value - a so-called
 'phantom type'. They're useful when you need a type (eg as the argument
 for a ForeignPointer) but no need for an actual value.

 You can of course create values of these types using 'undefined',
 'error' and friends, but this is perhaps not very useful most of the
 time :)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-28 Thread Austin Seipp
Excerpts from Galchin, Vasili's message of Mon Jul 28 21:14:56 -0500 2008:
 ok guys .. what is this phantom type concept? Is it a type theory thing or
 just Haskell type concept?
 
 Vasili

Phantom types are more of an idiom than anything else; they are types
with no real concrete representation, i.e. they only exist at compile
time, and not at runtime.

They can be used to hijack the type system, essentially. For example:

 data Expr = EInt  Int
   | EBool Bool
   | ECond Expr Expr Expr
   | EAdd Expr Expr
  deriving (Show)

This basically represents the constructs for a simple expression
language. However, wouldn't it be nice if we could say that 'EAdd' can
only take an 'EInt' or that ECond's first parameter must be 'EBool'
and check that at *compile* time? In this case, we can't. We would
have to check at runtime when we try to evaluate things that indeed,
the types fit together properly for our little 'expression language.'

But not all is lost.

With phantom types, we can 'hijack' the type system so that
it'll verify this for us. We can do this by simply making a newtype
over 'Expr' and giving it a type variable that does not show up on the
right side:

 newtype Expression a = E Expr
  deriving (Show)

In this case, the 'a' is the phantom type. It does not show up in the
constructors, so it does not exist at runtime.

Now all we simply have to do is 'lift' all of the constructors of Expr
into their own functions that stick the data into an 'Expression'
using the E constructor:

 intE :: Int - Expression Int
 intE = E . EInt

 boolE :: Bool - Expression Bool
 boolE = E . EBool

 condE :: Expression Bool 
   - Expression a 
   - Expression a
   - Expression a
 condE (E a) (E b) (E c) = E $ ECond a b c

 addE :: Expression Int - Expression Int - Expression Int
 addE (E a) (E b) = E $ EAdd a b

You'll notice: in the type signatures above, we give the phantom type
of Expression a concrete type such as 'Int' or 'Bool'.

What does this get is? It means that if we construct values via intE
and boolE, and then subsequently use them with condE or addE, we can't
use values of the wrong type in place of one another and the type system
will make sure of it.

For example:

$ ghci
...
Prelude :l phantom.lhs
[1 of 1] Compiling Main ( phantom.lhs, interpreted )
Ok, modules loaded: Main.
*Main let e1 = boolE True
*Main let e2 = intE 12
*Main let e3 = intE 21
*Main condE e1 e2 e3
E (ECond (EBool True) (EInt 12) (EInt 21))
*Main condE e2 e1 e3

interactive:1:6:  
 
Couldn't match expected type `Bool' against inferred type `Int'
  Expected type: Expression Bool
  Inferred type: Expression Int
In the first argument of `condE', namely `e2'
In the expression: condE e2 e1 e3
*Main

As you can see, we 'hijack' the type system so we can specify exactly
what type of 'Expression' functions like intE/boolE will return. We
then simply have other functions which operate over them, and also
specify *exactly* what kind of expression is necessary for them to
work. The phantom type never exists, it only is there to verify we're
doing the right thing.

That was a bit OT though.

In the case of empty data declarations, it's essentially the same
idea. It's just a type with no actual runtime representation. You can
exploit them to force invariants in your types or numerous other
things; a good example is type arithmetic which can be found on the wiki:

http://www.haskell.org/haskellwiki/Type_arithmetic

The example here is based off of Lennart's blog post about
representing DSLs in haskell, and he also shows an example of the same
thing which uses GADTs which allow you to do the same thing (roughly.)
So I'd say give the credit wholly to him. :)

http://augustss.blogspot.com/2007/06/representing-dsl-expressions-in-haskell.html

Austin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-27 Thread Galchin, Vasili
Hi Duncan and Brandon,

 I am  moving to the ForeignPtr strategy. However, I always try to learn
from where I am before going to a new approach. I have discovered by
debugging that the AIOCB peek is working; however, passing the peeked
AIOCB back to the caller(i.e. the test program) is not working .. please let
me try to demonstrate below. I have been staring at my Haskell code many,
many times  sigh ...


0)


IN PEEK CODE .. aioErrorCode = 115
IN PEEK CODE .. aioReturnValue = 0
aioWrite after aio_write
IN PEEK CODE .. aioErrorCode = 115
IN PEEK CODE .. aioReturnValue = 0
*aiocb dump***
fd = 3
opcode = 1
prio = 0
offset = 0
nbytes = 20
next = 0x
absprio = 0
policy = 0
errocode = 115   correct ... INPROGRESS errno
return value = 0

return from call of Haskell function aioWrite here
... below errocode has changed from 115 to 0 ... somehow my return AIOCB
is corrupting the state/value of AIOCB 

*aioWrite dumpAIOCB
*aiocb dump***
fd = 3
opcode = 0
prio = 0
offset = 0
nbytes = 20
next = 0x
absprio = 0
policy = 0
errocode = 0  incorrect Errno ... should
still be IN PROGRESS.
return value = 0

1) aioWrite ... the function marshalling(poke) and unmarshalling(peek) an
AIOCB:


aioWrite :: AIOCB - IO AIOCB
aioWrite aiocb = do
   allocaBytes (#const sizeof(struct aiocb)) $ \ p_aiocb - do
  poke p_aiocb aiocb

  putStrLn aioWrite before aio_write
  aiocb1 - peek p_aiocb
  dumpAIOCB aiocb1

  throwErrnoIfMinus1 aioWrite (c_aio_write  p_aiocb)
  aiocb - peek p_aiocb

  putStrLn aioWrite after aio_write
  aiocb - peek p_aiocb
  dumpAIOCB aiocb

--  putStrLn aioWrite after aio_write
--  aiocb1 - peek p_aiocb
--  dumpAIOCB aiocb1

  return (aiocb)

foreign import ccall safe aio.h aio_write
c_aio_write :: Ptr AIOCB - IO CInt


2) an AIOCB:

data LioOps = LioRead | LioWrite | LioNop


data AIOCB = AIOCB {

aioFd :: Fd,

aioLioOpcode :: Int,

aioReqPrio :: Int,

aioOffset :: FileOffset,

aioBuf :: Ptr Word8,

aioBytes :: ByteCount,

aioSigevent :: Sigevent,


-- Internal members

aioNext :: Ptr AIOCB,

aioAbsPrio :: Int,

aioPolicy :: Int,

aioErrorCode :: Int,

aioReturnValue :: ByteCount
}


3) poke/peek

instance Storable AIOCB where

sizeOf _ = (#const sizeof (struct aiocb))

alignment _ = 1

poke p_AIOCB (AIOCB aioFd aioLioOpcode aioReqPrio aioOffset aioBuf
aioBytes aioSigevent aioNext aioAbsPrio aioPolicy aioErrorCode
aioReturnValue) = do

   (#poke struct aiocb, aio_fildes) p_AIOCB aioFd

   (#poke struct aiocb, aio_lio_opcode) p_AIOCB aioLioOpcode

   (#poke struct aiocb, aio_reqprio) p_AIOCB aioReqPrio

   (#poke struct aiocb, aio_offset) p_AIOCB aioOffset

   (#poke struct aiocb, aio_buf) p_AIOCB aioBuf

   (#poke struct aiocb, aio_nbytes) p_AIOCB aioBytes

   (#poke struct aiocb, aio_sigevent) p_AIOCB aioSigevent

   (#poke struct aiocb, __next_prio) p_AIOCB aioNext

   (#poke struct aiocb, __abs_prio) p_AIOCB aioAbsPrio

   (#poke struct aiocb, __policy) p_AIOCB aioPolicy

   (#poke struct aiocb, __error_code) p_AIOCB aioErrorCode

   (#poke struct aiocb, __return_value) p_AIOCB aioReturnValue



peek p_AIOCB = do

   aioFd - (#peek struct aiocb, aio_fildes) p_AIOCB

   aioLioOpcode - (#peek struct aiocb, aio_lio_opcode) p_AIOCB

   aioReqPrio - (#peek struct aiocb, aio_reqprio) p_AIOCB

   aioOffset - (#peek struct aiocb, aio_offset) p_AIOCB

   aioBuf - (#peek struct aiocb, aio_buf) p_AIOCB

   aioBytes - (#peek struct aiocb, aio_nbytes) p_AIOCB

   aioSigevent - (#peek struct aiocb, aio_sigevent) p_AIOCB

   aioNext - (#peek struct aiocb, __next_prio) p_AIOCB

   aioAbsPrio - (#peek struct aiocb, __abs_prio) p_AIOCB

   aioPolicy - (#peek struct aiocb, __policy) p_AIOCB

   aioErrorCode - (#peek struct aiocb, __error_code) p_AIOCB
   putStrLn (IN PEEK CODE .. aioErrorCode =  ++ (show aioErrorCode))

   aioReturnValue - (#peek struct aiocb, __return_value) p_AIOCB
   putStrLn (IN PEEK CODE .. aioReturnValue =  ++ (show
aioReturnValue))

   return (AIOCB aioFd aioLioOpcode aioReqPrio aioOffset aioBuf aioBytes
aioSigevent aioNext aioAbsPrio aioPolicy aioErrorCode aioReturnValue)

Kind regards, Vasili






On Sun, Jul 20, 2008 at 6:51 AM, Duncan Coutts
[EMAIL PROTECTED]wrote:


 On Sat, 2008-07-19 at 23:55 -0500, Galchin, Vasili wrote:
  yes Duncan I am trying to pass-by-value. I am familiar with
  ForeignPtr; however, I don't comprehend what you and Brandon are
  suggesting to do. Could either of you provide a code illustration or
  point at existing code to illustrate your approach?

 Take a look at John Meacham's RSA example.

 So at the moment you're using using Storable and a Haskell record, say:

 data 

Re: [Haskell-cafe] carry state around ....

2008-07-21 Thread John Meacham
On Mon, Jul 21, 2008 at 01:05:48PM +1200, Richard A. O'Keefe wrote:
 I think it may be time for a little clarity about aoicb's.
 From the Single Unix Specification:
  The aio.h header shall define the aiocb structure
   which shall include AT LEAST the following members:
 int aio_fildes File descriptor.
 off_t   aio_offset File offset.
 volatile void  *aio_bufLocation of buffer.
 size_t  aio_nbytes Length of transfer.
 int aio_reqprioRequest priority offset.struct  
 sigevent aio_sigevent   Signal number and value.
 int aio_lio_opcode Operation to be performed.
  
 The AT LEAST here means that
  - a portable program may rely on these members being present
  - a portable program MUST assume that an unknown number of
additional members are also present
  - a portable program may freely copy such a record, but may
only pass it to a library function if that function is
expecting to initialise it

 For asynchronous I/O, this means that
  - you can allocate an aiocb object
  - an aiocb passed to aio_suspend, aio_error,
aio_return, or aio_cancel should have been
filled in by aio_read or aio_write and should
be EXACTLY THE SAME object, not a copy of it.

Yes. This is pretty standard as far as what you can count on in terms of
standard C structures. The method I use in the RSA.hsc module I posted
is compatible with these assumptions. Generally this is pretty much
exactly the thing hsc2hs was made to solve. 

Just a note, if you are doing manual explicit frees of the aiocb
structure then you only need a 'Ptr', if you want the structure to be
automatically garbage collected when all haskell references to it
disappear, then you need to use 'ForeignPtr'.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-20 Thread John Meacham
In order to write portable code that accesses C structures, you need to
write a c shim, or better, use the 'hsc2hs' tool to produce portable
code. For an example, you can see my OpenSSL binding code in 

http://repetae.net/repos/ginsu/RSA.hsc

in particular the 'createPkey' function. the #ptr construct gets a
pointer to a member of a C structure, and #peek and #poke let you read
and set members. You should use (#const sizeof(struct foo)) to determine
how much memory you need to allocate for a structure. (unless the API
you are binding specifies some other allocation method)

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-20 Thread Duncan Coutts

On Sat, 2008-07-19 at 23:55 -0500, Galchin, Vasili wrote:
 yes Duncan I am trying to pass-by-value. I am familiar with
 ForeignPtr; however, I don't comprehend what you and Brandon are
 suggesting to do. Could either of you provide a code illustration or
 point at existing code to illustrate your approach?

Take a look at John Meacham's RSA example.

So at the moment you're using using Storable and a Haskell record, say:

data AIOCB = AIOCB { 
...
  }

and we're suggesting instead:

newtype AIOCB = AIOCB (ForeignPtr AIOCB)

then to access a member use hsc2hs:

getBlah :: AIOCB - IO Blah
getBlah (AIOCB fptr) =
  withForeignPtr fptr $ \ptr - {# peek aiocb,blah #} ptr

So you only access the parts you need and keep the aiocb C struct
allocated on the heap (use mallocForeignPtr).

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-20 Thread Richard A. O'Keefe

I think it may be time for a little clarity about aoicb's.
From the Single Unix Specification:
 The aio.h header shall define the aiocb structure
  which shall include AT LEAST the following members:
int aio_fildes File descriptor.
off_t   aio_offset File offset.
volatile void  *aio_bufLocation of buffer.
size_t  aio_nbytes Length of transfer.
int aio_reqprioRequest priority offset.struct  
sigevent aio_sigevent   Signal number and value.

int aio_lio_opcode Operation to be performed.
 
The AT LEAST here means that
 - a portable program may rely on these members being present
 - a portable program MUST assume that an unknown number of
   additional members are also present
 - a portable program may freely copy such a record, but may
   only pass it to a library function if that function is
   expecting to initialise it

For asynchronous I/O, this means that
 - you can allocate an aiocb object
 - an aiocb passed to aio_suspend, aio_error,
   aio_return, or aio_cancel should have been
   filled in by aio_read or aio_write and should
   be EXACTLY THE SAME object, not a copy of it.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-20 Thread Brandon S. Allbery KF8NH


On 2008 Jul 20, at 21:05, Richard A. O'Keefe wrote:


For asynchronous I/O, this means that
- you can allocate an aiocb object
- an aiocb passed to aio_suspend, aio_error,
  aio_return, or aio_cancel should have been
  filled in by aio_read or aio_write and should
  be EXACTLY THE SAME object, not a copy of it.



Right, hence a ForeignPtr which is mostly opaque.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-20 Thread Galchin, Vasili
Thank you Duncan for your example. I will also read the RSA code.

Regards, Vasili


On Sun, Jul 20, 2008 at 6:51 AM, Duncan Coutts [EMAIL PROTECTED]
wrote:


 On Sat, 2008-07-19 at 23:55 -0500, Galchin, Vasili wrote:
  yes Duncan I am trying to pass-by-value. I am familiar with
  ForeignPtr; however, I don't comprehend what you and Brandon are
  suggesting to do. Could either of you provide a code illustration or
  point at existing code to illustrate your approach?

 Take a look at John Meacham's RSA example.

 So at the moment you're using using Storable and a Haskell record, say:

 data AIOCB = AIOCB {
...
  }

 and we're suggesting instead:

 newtype AIOCB = AIOCB (ForeignPtr AIOCB)

 then to access a member use hsc2hs:

 getBlah :: AIOCB - IO Blah
 getBlah (AIOCB fptr) =
  withForeignPtr fptr $ \ptr - {# peek aiocb,blah #} ptr

 So you only access the parts you need and keep the aiocb C struct
 allocated on the heap (use mallocForeignPtr).

 Duncan


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] carry state around ....

2008-07-19 Thread Galchin, Vasili
hello,


Following is more of a criticism of Linux implementation of the Posix
real-time extension of asynchronous I/O if not interesting please skip.
The central data structure for Posix AIO is an aiocb. In any case, the Linux
implementors added to the aiocb:

/* Asynchronous I/O control block.  */
struct aiocb
{
  int aio_fildes;   /* File desriptor.  */
  int aio_lio_opcode;   /* Operation to be performed.  */
  int aio_reqprio;  /* Request priority offset.  */
  volatile void *aio_buf;   /* Location of buffer.  */
  size_t aio_nbytes;/* Length of transfer.  */
  struct sigevent aio_sigevent; /* Signal number and value.  */

  /* Internal members.  */ 
  struct aiocb *__next_prio;
  int __abs_prio;
  int __policy;
  int __error_code;
  __ssize_t __return_value;

#ifndef __USE_FILE_OFFSET64
  __off_t aio_offset;   /* File offset.  */
  char __pad[sizeof (__off64_t) - sizeof (__off_t)];
#else
  __off64_t aio_offset; /* File offset.  */
#endif
  char __unused[32];
};

My viewpoint is that the above Internal members must be carried around
in a Haskell program. Am I correct?? If I am correct, then the Linux
implementation of Posix AIO is not portable to say Solaris? In hindsight, if
I am correct, it seems that the Linux implementation of AIO should use the
ordered pair (pid, fd) to reference the internal members and leave the
aiocb clean?

Very kind regards, Vasili
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-19 Thread Brandon S. Allbery KF8NH


On 2008 Jul 19, at 2:40, Galchin, Vasili wrote:

My viewpoint is that the above Internal members must be carried  
around in a Haskell program. Am I correct?? If I am correct, then  
the Linux implementation of Posix AIO is not portable to say  
Solaris? In hindsight, if I am correct, it seems that


You are correct --- but Solaris also has its own addenda, and its  
standard fields are not at the same offsets as in the Linux aiocb.   
The only safe way to do this is to use an opaque aiocb on the Haskell  
side and accessors in C via FFI.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-19 Thread Duncan Coutts

On Sat, 2008-07-19 at 01:40 -0500, Galchin, Vasili wrote:
 hello,
 
 
 Following is more of a criticism of Linux implementation of the
 Posix real-time extension of asynchronous I/O if not interesting
 please skip. The central data structure for Posix AIO is an aiocb. In
 any case, the Linux implementors added to the aiocb:

[..]

 My viewpoint is that the above Internal members must be carried
 around in a Haskell program. Am I correct?? If I am correct, then the
 Linux implementation of Posix AIO is not portable to say Solaris? In
 hindsight, if I am correct, it seems that the Linux implementation of
 AIO should use the ordered pair (pid, fd) to reference the internal
 members and leave the aiocb clean?

Although it is different between platforms it is still portable. When
you allocate memory in C for the aiocb struct you would use
sizeof(aiocb). That's portable even if the size is different on Linux vs
Solaris. Then members are only accessed by name which is again portable.

Your problem perhaps is that you're trying to convert an aiocb into a
pure haskell version and convert it back and expect to retain all the
information. I think that is a mistake. Don't pass the aiocb's by value,
pass them by reference. Use a ForeignPtr and just access the members you
need whenever you need them.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-19 Thread Duncan Coutts

On Sat, 2008-07-19 at 10:45 -0400, Brandon S. Allbery KF8NH wrote:
 
 On 2008 Jul 19, at 2:40, Galchin, Vasili wrote:
 
  My viewpoint is that the above Internal members must be carried
  around in a Haskell program. Am I correct?? If I am correct, then
  the Linux implementation of Posix AIO is not portable to say
  Solaris? In hindsight, if I am correct, it seems that 
 
 
 You are correct --- but Solaris also has its own addenda, and its
 standard fields are not at the same offsets as in the Linux aiocb.
  The only safe way to do this is to use an opaque aiocb on the Haskell
 side and accessors in C via FFI.

You can do field accessors using an FFI pre-processor like c2hs or
hsc2hs which will calculate the correct field offsets for the current
platform. No need for C wrappers.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-19 Thread Galchin, Vasili
Brandon,

  You lost me  can you explain what an opaque aiocb would look like?

Vasili

On Sat, Jul 19, 2008 at 9:45 AM, Brandon S. Allbery KF8NH 
[EMAIL PROTECTED] wrote:


 On 2008 Jul 19, at 2:40, Galchin, Vasili wrote:

 My viewpoint is that the above Internal members must be carried around
 in a Haskell program. Am I correct?? If I am correct, then the Linux
 implementation of Posix AIO is not portable to say Solaris? In hindsight, if
 I am correct, it seems that


 You are correct --- but Solaris also has its own addenda, and its standard
 fields are not at the same offsets as in the Linux aiocb.  The only safe way
 to do this is to use an opaque aiocb on the Haskell side and accessors in C
 via FFI.

 --
 brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
 system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
 electrical and computer engineering, carnegie mellon universityKF8NH



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-19 Thread Brandon S. Allbery KF8NH


On 2008 Jul 19, at 16:42, Galchin, Vasili wrote:

  You lost me  can you explain what an opaque aiocb would  
look like?



In Haskell, it's a ForeignPtr --- you can't see inside it except by  
FFI calls.  Although Duncan is correct and you can use an FFI  
preprocessor to access the portable fields, and simply not provide  
access to the rest from Haskell.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] carry state around ....

2008-07-19 Thread Galchin, Vasili
yes Duncan I am trying to pass-by-value. I am familiar with ForeignPtr;
however, I don't comprehend what you and Brandon are suggesting to do. Could
either of you provide a code illustration or point at existing code to
illustrate your approach?

Kind regards, Vasili

On Sat, Jul 19, 2008 at 8:28 AM, Duncan Coutts [EMAIL PROTECTED]
wrote:


 On Sat, 2008-07-19 at 01:40 -0500, Galchin, Vasili wrote:
  hello,
 
 
  Following is more of a criticism of Linux implementation of the
  Posix real-time extension of asynchronous I/O if not interesting
  please skip. The central data structure for Posix AIO is an aiocb. In
  any case, the Linux implementors added to the aiocb:

 [..]

  My viewpoint is that the above Internal members must be carried
  around in a Haskell program. Am I correct?? If I am correct, then the
  Linux implementation of Posix AIO is not portable to say Solaris? In
  hindsight, if I am correct, it seems that the Linux implementation of
  AIO should use the ordered pair (pid, fd) to reference the internal
  members and leave the aiocb clean?

 Although it is different between platforms it is still portable. When
 you allocate memory in C for the aiocb struct you would use
 sizeof(aiocb). That's portable even if the size is different on Linux vs
 Solaris. Then members are only accessed by name which is again portable.

 Your problem perhaps is that you're trying to convert an aiocb into a
 pure haskell version and convert it back and expect to retain all the
 information. I think that is a mistake. Don't pass the aiocb's by value,
 pass them by reference. Use a ForeignPtr and just access the members you
 need whenever you need them.

 Duncan


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe