Re: Data.Dynamic and dynamically loaded code

2004-06-14 Thread Donald Bruce Stewart
simonmar:
> On 10 June 2004 05:32, Donald Bruce Stewart wrote:
> 
> > The problem appears to be in the hash keys of the type representation
> > used to compare to types for equality. A dynamic value in the
> > (statically compiled) application never has the same key as its
> > equivalent type in the dynamically loaded code.  The type in the
> > dynamically-loaded plugin code is never recognised as having the same
> > type as in the application (static) code.
> > 
> > The following comment from Data.Typeable seems to be relevant:
> > 
> > -- In GHC we use the RTS's genSym function to get a new unique,
> > -- because in GHCi we might have two copies of the Data.Typeable
> > -- library running (one in the compiler and one in the running
> > -- program), and we need to make sure they don't share any keys.
> > --
> > -- This is really a hack.  A better solution would be to
> > centralise the -- whole mutable state used by this module, i.e.
> > both hashtables.
> > But 
> > -- the current solution solves the immediate problem, which is
> > that 
> > -- dynamics generated in one world with one type were erroneously
> > -- being recognised by the other world as having a different type.
> 
> This is exactly the problem.  To fix it, you need to implement the
> suggestion from the comment: i.e. somehow make it so that there is only
> one copy of the hash table rather than two.  You could do this by
> keeping the hash table in a variable in the RTS, perhaps.

Ok! That's what I'll do.
  
> I don't know why you get differing String representation of types,
> though.  It doesn't have anything to do with Core types, I'm pretty
> sure.

I've fixed this particular issue by reimplementing the Eq for TypeRep
and TyCon in Data.Typeable to use the String rep for equality of
TypeReps, rather than using show to compare two TypeReps, in
Dynamic.fromDyn. Fixing Eq at a lower level than Dynamic seemed to do
the trick. Still not sure why using show in fromDyn caused the two
different representations, though.

-- Don
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Data.Dynamic and dynamically loaded code

2004-06-14 Thread Simon Marlow
On 10 June 2004 05:32, Donald Bruce Stewart wrote:

> The problem appears to be in the hash keys of the type representation
> used to compare to types for equality. A dynamic value in the
> (statically compiled) application never has the same key as its
> equivalent type in the dynamically loaded code.  The type in the
> dynamically-loaded plugin code is never recognised as having the same
> type as in the application (static) code.
> 
> The following comment from Data.Typeable seems to be relevant:
> 
> -- In GHC we use the RTS's genSym function to get a new unique,
> -- because in GHCi we might have two copies of the Data.Typeable
> -- library running (one in the compiler and one in the running
> -- program), and we need to make sure they don't share any keys.
> --
> -- This is really a hack.  A better solution would be to
> centralise the 
> -- whole mutable state used by this module, i.e. both hashtables.
> But 
> -- the current solution solves the immediate problem, which is
> that 
> -- dynamics generated in one world with one type were erroneously
> -- being recognised by the other world as having a different type.

This is exactly the problem.  To fix it, you need to implement the
suggestion from the comment: i.e. somehow make it so that there is only
one copy of the hash table rather than two.  You could do this by
keeping the hash table in a variable in the RTS, perhaps.

I don't know why you get differing String representation of types,
though.  It doesn't have anything to do with Core types, I'm pretty
sure.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Data.Dynamic and dynamically loaded code

2004-06-09 Thread Donald Bruce Stewart
(lengthy)

Hey,

In the hs-plugins library I'm using Data.Dynamic to provide runtime type
checking of plugin values when they are loaded. There is a problem,
however: when using fromDyn/fromDynamic to check the type of the
plugin's value against the type the application loading the plugin
expects, they always report that types are unequal, even if they are the
same type on both sides.

So I'm reporting a limitation of the existing Data.Dynamic, and have a
couple of questions about why this exists.

The problem appears to be in the hash keys of the type representation
used to compare to types for equality. A dynamic value in the
(statically compiled) application never has the same key as its
equivalent type in the dynamically loaded code.  The type in the
dynamically-loaded plugin code is never recognised as having the same
type as in the application (static) code.

The following comment from Data.Typeable seems to be relevant:

-- In GHC we use the RTS's genSym function to get a new unique,
-- because in GHCi we might have two copies of the Data.Typeable
-- library running (one in the compiler and one in the running
-- program), and we need to make sure they don't share any keys.  
--
-- This is really a hack.  A better solution would be to centralise the
-- whole mutable state used by this module, i.e. both hashtables.  But
-- the current solution solves the immediate problem, which is that
-- dynamics generated in one world with one type were erroneously
-- being recognised by the other world as having a different type.

An example. The following code uses eval() to compile the string "7 + 8"
to object code, and dynamically load the result.

  main = do i <- eval "7 + 8 :: Int" :: IO Int
putStrLn $ show i

When checking the dynamically loaded type using fromDynamic, we have
 /= , which is obviously wrong. Running the equivalent code in
GHCi doesn't generate this error, nor does statically linked code. It is
only if we loadObj the plugin and check it against a type statically
compiled into the application doing the loading.

I currently work around this with a reimplemented Data.Dynamic that
compares the string representations of the types, which works mostly (so
that "Int" == "Int", in the above code). However, when there is no
explicit type declaration in the dynamically loaded code, for
non-simple types, the *string* type representations differ. I.e. in the
following code:

main = do fn <- eval "\\(x::Int) -> (x,x)" :: IO (Int -> (Int,Int))
  putStrLn $ show (fn 7)

we have type "-> Int (Int,Int)" doesn't match "Int -> (Int,Int)" (which
looks like a Core type in the first case). And for:

i <- eval "map (+1) [0..10::Int]" :: [Int]

we have "[] Int" /= "[Int]". So, the string comparison of types doesn't
always work.


So... for safe dynamically loaded plugins we need to fix Data.Dynamic to
provide the a unique integer key for types across both static and
dynamic code, I think. Does that seem like reasonable? 

And a question: why do we get different strings from TypeRep's when the
type is inferred? I can see that we are getting Core type reps, but why?
I would have thought that the TypeRep would still have to be constructed
in the same way as in an explicit declaration.

-- Don
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users