[Haskell-beginners] Why is this type ambiguous?

Daniel Fischer daniel.is.fischer at web.de
Mon Oct 26 19:11:20 EDT 2009


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




More information about the Beginners mailing list