[Haskell] Re: Initialisation without unsafePerformIO

Abraham Egnor abe.egnor at gmail.com
Fri Jun 4 13:56:34 EDT 2004


I don't see how this technique can be at all safe:

instance ReflectStorable s => Reflect (Stable s a) a where
  reflect = unsafePerformIO $
    do a <- deRefStablePtr p
       freeStablePtr p
       return (const a)
    where p = reflectStorable (undefined :: s p)

reify :: a -> (forall s. Reflect s a => s -> w) -> w
reify (a :: a) k = unsafePerformIO $
    do p <- newStablePtr a
       reifyStorable p (\(_ :: s p) -> k' (undefined :: Stable s a))
    where k' (s :: s) = (reflect :: s -> a) `seq` return (k s)

The above means that a StablePtr will be allocated once per reify and
destroyed once per reflect; I don't see how the code can guarantee
that there will be only one reflect per reify.  In fact, it seems
quite likely that there will be far more reflects than reifys.

On Fri, 4 Jun 2004 03:35:25 -0700, John Meacham <john at repetae.net> wrote:
> 
> On Fri, Jun 04, 2004 at 12:35:14AM -0700, Ashley Yakeley wrote:
> > In article <20040601163515.GA8357 at momenergy.repetae.net>,
> >  John Meacham <john at repetae.net> wrote:
> >
> > > I am a fan of allowing top level declarations of the form:
> > >
> > > foo <- newIORef "foo"
> > >
> > > which would behave as an initializer, with the semantics being that it
> > > be evaluated at most once before foos first use. (so it could be
> > > implemented via unsafePerformIO or as an init section run before main).
> > >
> > > The
> > > {-# NOINLINE foo #-}
> > > foo = unsafePeformIO $ newIORef "foo"
> > >
> > > idiom is so common and useful, it should have some compiler support. It
> > > is 'clean' too, since all we are doing is extending the "world" with new
> > > state, but in a much cleaner/safer way then writing to a file or environment
> > > variable or other methods of storing state in the world.
> >
> > Clean it is not:
> >
> > foo :: a
> > foo <- newIORef undefined
> >
> > writeChar :: Int -> IO ()
> > writeChar x = writeIORef foo x
> >
> > readString :: IO String
> > readString = readIORef foo
> >
> > cast :: Char -> IO String
> > cast c = (writeChar c) >> readString
> 
> Yeah, such an extension would need to ensure initializers are monomorphic. another
> advantage of a special syntax rather than unsafePerformIO.
> 
> 
>         John
> 
> --
> John Meacham - ⑆repetae.net⑆john⑈
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>


More information about the Haskell mailing list