
import Foreign import Foreign.C genericCast :: (Storable a, Storable b) => a -> IO b genericCast v = let dummy = undefined size = max (sizeOf v) (sizeOf dummy) in if False then return dummy else allocaBytes size $ \p -> poke p v >> peek (castPtr p) ---- Code above gives me this: Ambiguous type variable `a' in the constraint: `Storable a' arising from a use of `sizeOf' at src/Bindings/C.hs:28:27-38 ---- It seems to refer to '(sizeOf dummy)'. But isn't the type of 'dummy' defined by 'return dummy' beeing a possible return value (and, so, dummy :: b)? Thanks, Maurício

I have no idea what you're trying to do here (looks as if you just
want to recreate Unsafe.Coerce.unsafeCoerce?)
However, dummy is first used an 'a' and then as a 'b', so that can't work.
Next, in sizeOf undefined, undefined does not provide enough
information about that type undefined should be. Although the compiler
can infer that sizeOf undefined must be of the same type as sizeOf v,
that's not enough, it needs to know the type of undefined (I guess you
want it to be the same type as v?)
Can be fixed like:
genericCast :: (Storable a, Storable b) => a -> IO b
genericCast v = let
size = max (sizeOf v) (sizeOf $ undefined `asTypeOf` v)
in if False
then return undefined
else allocaBytes size $ \p -> poke p v >> peek (castPtr p)
But... feels insanely hacky, and is not something a beginner should
attempt to play with I guess ;)
2009/10/26 Maurício CA
import Foreign import Foreign.C
genericCast :: (Storable a, Storable b) => a -> IO b genericCast v = let dummy = undefined size = max (sizeOf v) (sizeOf dummy) in if False then return dummy else allocaBytes size $ \p -> poke p v >> peek (castPtr p)
----
Code above gives me this:
Ambiguous type variable `a' in the constraint: `Storable a' arising from a use of `sizeOf' at src/Bindings/C.hs:28:27-38
----
It seems to refer to '(sizeOf dummy)'. But isn't the type of 'dummy' defined by 'return dummy' beeing a possible return value (and, so, dummy :: b)?
Thanks, Maurício
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I have no idea what you're trying to do here (looks as if you just want to recreate Unsafe.Coerce.unsafeCoerce?)
Yes, except that it works with Storables only and is safe against runtime corruption. Evil, but can save you from worst FFI hacks.
However, dummy is first used an 'a' and then as a 'b', so that can't work.
Where is dummy used as 'a'? The only place with a specific type I used it is in 'return dummy', and it's there exactly to "get" that 'b' type.
Although the compiler can infer that sizeOf undefined must be of the same type as sizeOf v, (...)
size = max (sizeOf v) (sizeOf $ undefined `asTypeOf` v)
No, it's not the same type! The idea is that 'size' value should be the bigger of 'a' and 'b' sizes, so that I guarantee enough memory will be allocated for the cast.
But... feels insanely hacky, and is not something a beginner should attempt to play with I guess ;)
I have an unusual experience with Haskell. I used it a lot, but mainly with FFI. So, I'm an expert in FFI -- I have my own package of hsc2hs macros :) -- but I have no understanding of the type system, except for just the basics. Maurício
import Foreign import Foreign.C
genericCast :: (Storable a, Storable b) => a -> IO b genericCast v = let dummy = undefined size = max (sizeOf v) (sizeOf dummy) in if False then return dummy else allocaBytes size $ \p -> poke p v >> peek (castPtr p)

Am Montag 26 Oktober 2009 23:24:26 schrieb Maurício CA:
import Foreign import Foreign.C
genericCast :: (Storable a, Storable b) => a -> IO b genericCast v = let dummy = undefined size = max (sizeOf v) (sizeOf dummy) in if False then return dummy else allocaBytes size $ \p -> poke p v >> peek (castPtr p)
----
Code above gives me this:
Ambiguous type variable `a' in the constraint: `Storable a' arising from a use of `sizeOf' at src/Bindings/C.hs:28:27-38
----
It seems to refer to '(sizeOf dummy)'. But isn't the type of 'dummy' defined by 'return dummy' beeing a possible return value (and, so, dummy :: b)?
No. let-bindings are polymorphic, so dummy :: forall a. a {-# LANGUAGE ScopedTypeVariables #-} -- This is unsafe, don't use genericCast :: forall a b. (Storable a, Storable b) => a -> IO b genericCast v = let dummy :: b dummy = undefined ...
Thanks, Maurício

But isn't the type of 'dummy' defined by 'return dummy' beeing a possible return value (and, so, dummy :: b)?
No. let-bindings are polymorphic, so dummy :: forall a. a
Oh, I once learned that some code of mine didn't work because lambda bindings are monomorphic. Now I can use it for good. genericCast :: (Storable a, Storable b) => a -> IO b genericCast v = return undefined >>= \dummy -> allocaBytes (max (sizeOf v) (sizeOf dummy)) $ \p -> poke p v >> if False then return dummy else peek (castPtr p) In ghci: > let a = 4 :: WordPtr > b <- genericCast a :: IO (Ptr ()) > b 0x00000004 Thanks! Maurício
participants (3)
-
Daniel Fischer
-
Maurício CA
-
Peter Verswyvelen