ANN: H98 FFI Addendum 1.0, Release Candidate 10
Manuel M T Chakravarty
chak at cse.unsw.edu.au
Thu Jul 3 22:37:27 EDT 2003
Ross Paterson <ross at soi.city.ac.uk> wrote,
> On Thu, Jul 03, 2003 at 06:51:31PM +1000, Manuel M T Chakravarty wrote:
> > Ross Paterson <ross at soi.city.ac.uk> wrote,
> >
> > > The new wording:
> > >
> > > \code{unsafePerformIO} may compromise typing; to avoid this, the programmer
> > > should ensure that the result of \code{unsafePerformIO} has a monomorphic
> > > type.
> > >
> > > rules out the following:
> > >
> > > my_hash :: Storable a => a -> Int
> > > my_hash a = fromIntegral $ unsafePerformIO $
> > > allocaBytes (sizeof a) $ \p -> do
> > > let size = fromIntegral (sizeOf a)
> > > c_memset p 0 size
> > > poke p a
> > > hash_bytes p size
> > >
> > > foreign import ccall unsafe "memset"
> > > c_memset :: Ptr a -> CInt -> CSize -> IO ()
> > > foreign import ccall unsafe
> > > hash_bytes :: Ptr a -> CSize -> IO CInt
> >
> > Why is this ruled out? hash_bytes returns a `CInt', which
> > is a monomorphic type.
>
> The argument of unsafePerformIO has type forall a. Storable a => a -> CInt
Hmm, maybe we are talking about different things, but the
argument to `unsafePerformIO' must be of the form `IO a',
doesn't it. Moreover, the above code applies `fromIntegral'
to the result of `unsafePerformIO'. So, the result of
`unsafePerformIO' must be an integral type.
> > > Manuel writes:
> > > > However, it is possible to construct examples that are deterministic,
> > > > but still dubious from a typing perspective. Let's assume a C routine
> > > >
> > > > void *foo();
> > > >
> > > > that *always returns the same pointer* to a buffer area. To
> > > > bind this in Haskell as
> > > >
> > > > foreign import ccall foo :: Ptr a
> > > >
> > > > is problematic[1].
> > >
> > > (a) It's constant across a run of the program, but its value still depends
> > > on the environment, and
> >
> > Yes, and that's nothing that we want to rule out. A
> > standard idiom for obtaining constant values from C is
> >
> > -= In C land =-
> >
> > int my_const ()
> > {
> > ...
> > return ...;
> > }
> >
> > -= In Haskell land =-
> >
> > const :: Int
> > const = unsafePerformIO my_const
> >
> > foreign import ccall my_const :: IO Int
> >
> > All that's required here is that my_const() is constant
> > within a program run.
>
> Shouldn't it be constant in a global sense, e.g. getpid wouldn't be allowed?
No, I don't think so. As long as it is constant for all
observations that the program can make, I don't see any
semantic problems.
Manuel
More information about the FFI
mailing list