At Tue, 21 Jun 2011 00:35:46 -0700 (PDT), o...@okmij.org wrote: > > > I have implemented type-level TYPEREP (along with a small library for > higher-order functional programming at the type level). Overlapping > instances may indeed be avoided. The library does not use functional > dependencies either. > > http://okmij.org/ftp/Haskell/TTypeable/
This is pretty cool. One question I have is why you need UndecidableInstances. If we got rid of the coverage condition, would your code be able to work without relying on contexts for instance selection? Now I understand the reference to the ML paper. If you were to implement this in GHC you would encode the TC_code as the packge, module, and type name, letter by letter? (Or bit by bit since symbols can contain unicode?) Or could you use interface hashes (or whatever those hex numbers are when you run ghc-pkg -v)? How would you make this safe for dynamic loading? Would you have to keep track of all the package/module names that have been linked into the program and/or loaded, and not allow duplicates? Is dynamic unloading of code ever possible? Or at least is re-loading possible, since that appears to be key for debugging web servers and such? Finally, how do you express constraints in contexts using type families? For example, say I wanted to implement folds over tuples. With fundeps (and undecidable instances, etc.), I would use a proxy type of class Function2 to represent the function: {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} class Function2 f a b r | f a b -> r where funcall2 :: f -> a -> b -> r -- An example, to show something of class Show and put the result in -- a list endo: data PolyShows = PolyShows instance (Show a) => Function2 PolyShows ([[Char]] -> [[Char]]) a ([[Char]] -> [[Char]]) where funcall2 _ start a = start . (show a :) -- Define a class for folds, as well as an instance for each tuple size: class TupleFoldl f z t r | f z t -> r where tupleFoldl :: f -> z -> t -> r instance TupleFoldl f z () z where tupleFoldl _ z _ = z instance (Function2 f z v0 r1, Function2 f r1 v1 r2) => TupleFoldl f z (v0,v1) r2 where tupleFoldl f z (v0,v1) = funcall2 f (funcall2 f z v0) v1 instance (Function2 f z v0 r1, Function2 f r1 v1 r2, Function2 f r2 v2 r3) => TupleFoldl f z (v0,v1,v2) r3 where tupleFoldl f z (v0,v1,v2) = funcall2 f (funcall2 f (funcall2 f z v0) v1) v2 -- -- ... and so on ... Now I can run: >>> tupleFoldl PolyShows (id::[String]->[String]) (1,2) [] ["1","2"] In your case, how do I define an Apply instance equivalent to PolyShows? Moreover, the fundep code above depends on the Function2 constraints to make things work out correctly. It also has the nice property that ghc can figure out many of the types automatically. You have to specify id's type, but ghc figures out the type of [], figures out the return type, and deals with 1 and 2 being (Num a => a). Now is it the case that to do this with TYPEREP, you have to add an internal class to express the constraints, and just pass extra arguments to the class in a wrapper function? Presumably you then have a bunch of ~ constraints. Does the type inference work as well? It's a bit more typing, but if you can do it without undecidable instances, or even with undecidable instances but keeping a bounded context stack depth, then it would definitely be worth it. With fundeps and undecidable instances, if I use the default context stack depth of 21, my left and right folds crap out at 10 and 13 element tuples, respectively. David _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime