[Haskell-cafe] Re: Dynamically find out instances of classes (pluginsystem for haskell)

2007-11-22 Thread ChrisK
the standard way to do that is use an existential wrapper:

(This needs -fglasgow-exts or some flags)

 module Main where
 
 class Interface x where
   withName :: x - String
 
 data A = A String
 
 instance Interface A where
   withName (A string) =  Interface A with  ++ string ++  
 
 data B = B Int
 
 instance Interface B where
   withName (B int) =  Interface B with  ++ show int ++  
 
 data WrapInterface where
WrapInterface :: forall z. Interface z = z - WrapInterface
 
 a :: A
 a = A seven
 
 b :: B
 b = B 7
 
 listOfWrapInterface :: [WrapInterface]
 listOfWrapInterface = [ WrapInterface a
   , WrapInterface b
   , WrapInterface (A ())
   , WrapInterface (B (-2007))
   ]
 
 nameOfWrapped :: WrapInterface - String
 nameOfWrapped (WrapInterface q) = withName q
 
 instance Interface WrapInterface where
   withName = nameOfWrapped
 
 main = do
   putStrLn (show (map nameOfWrapped listOfWrapInterface))
   putStrLn (show (map withName listOfWrapInterface))
 

In ghci this prints:

*Main main
[ Interface A with seven , Interface B with 7 , Interface A with ()
, Interface B with -2007 ]
[ Interface A with seven , Interface B with 7 , Interface A with ()
, Interface B with -2007 ]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Dynamically find out instances of classes (pluginsystem for haskell)

2007-11-22 Thread Jason Dusek
ChrisK [EMAIL PROTECTED] wrote:
 the standard way to do that is use an existential wrapper:

Does this relate to the basket of fruit problem in object
oriented languages?

You created the existential wrapper to allow a multimorphic
list type?

-- 
_jsn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Dynamically find out instances of classes (pluginsystem for haskell)

2007-11-22 Thread ChrisK
Jason Dusek wrote:
 ChrisK [EMAIL PROTECTED] wrote:
 the standard way to do that is use an existential wrapper:
 
 Does this relate to the basket of fruit problem in object
 oriented languages?
 
 You created the existential wrapper to allow a multimorphic
 list type?
 

When you access the wrapped data then *_ONLY_* thing you can do with it is via
the type class(es) that the GADT was wrapping.

The example I gave had a single type class:

 data WrapInterface where
WrapInterface :: forall z. Interface z = z - WrapInterface
 

One could have multiple interfaces:

 data WrapInterface where
WrapInterface :: (Interface z,Show z,Num z) = z - WrapInterface
 

One could have more than one piece of data, note that WrapInterface takes three
parameters:

 data WrapInterface where
WrapInterface :: Interface z = z - z - z - WrapInterface


One could do both:
 data WrapInterface where
   WrapInterface :: (Interface z1, Show z2,Num z3) =
 z1 - z2 - z3 - WrapInterface

And so on.  You can even write something like: data WrapInterface' where
 WrapInterface' :: a - (a-String) - WrapInterface'
 
 listExample = [ WrapInterface' Hello (show . (++ World))
   , WrapInterface' 17 (show . succ)
   , WrapInterface' True (show . not)
   ]
 
 apply :: WrapInterface' - String
 apply (WrapInterface' item function) = function item
 
 main = do
   putStrLn (show (map apply listExample))

Now a WrapInterface' holds item a and a function a-String.  When you unwrap
this in a case statement you can then apply the function to the item to get the
String.  The output in ghci is:

*Main main
[\HelloWorld\,18,False]

-- 
Chris

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe