RE: [Haskell-cafe] generics question, logical variables
Hi Frederik, [I call this "the dreadful lack of kind polymorphism strikes back" :-)] I put SPJ on cc; perhaps he can suggest a way to improve in this area. Based on input, I could try to work on this issue in the not so remote future. Let me briefly recapitulate. My recollection is that deriving works for Typeable, Tyepable1, ..., if all type parameters are of type kind "*". Whenever you can derive a Typeablen instance with n > 0, you can instead ask for Typeable to be derived. The reason why you cannot get both a Typeable and say a Typeable42 instance is that there are generic instances for getting an "n-1 instance" from the "n instance". However, this is also precisely the reason why you don't want them both. That is, you get everything you can ask for, if you have the "n instance" for the actual arity of the type constructor in question. (Getting a smaller n or no n just means that you limit polymorphic type case.) Recall that you *may* need a n>0 instance if you want to do polymorphic type case according to the SYB2 paper. As long as you are fine with monomorphic generic function extension, the plain Typeable instance should be fine. However, the real limitation is here, *indeed*, as said, that GHC does not derive Typeable[1|2|...] for parameter kinds other than "*". This was the reason that I had to hand-code some Typeable instances in your original example. Let us also be honest about another limitation of the current deriving code. "deriving Data" gives you Data instances that do *not* support polymorphic type case. That is the following code prints 0, 1, 0 whereas you may expect 0, 1, 2. newtype Foo x = Foo x deriving (Typeable, Data) f :: Data a => a -> Int f = const 0 `ext1Q` (\(_::Maybe x) -> 1) `ext1Q` (\(_::Foo y) -> 2) main = do print $ f True print $ f (Just True) print $ f (Foo (Just True)) This is the reason that I had to handcode some Data instances in your original example, which wasn't hard BTW. We thought that these two limitations were Ok since we didn't expect people to write many polymorphic datatype constructors on which SYB should work. Sounds like a feature request. Now I wonder how much work it is to improve the situation. We need to make the GHC deriving code a bit more kind-aware. I guess we are still not at the point where we want to add kind polymorphism to Haskell? Would be a nice topic for future work on SYB. Clearly, the GH folks have done splendid work in this area. Getting full-blown kind polymorphism in normal Haskell though seems to be less of a topic, simply because we do not have many scenarios around that would *really* require it. Does anyone want to speak up and mention scenarios that would benefit from kind polymorphism? (In Haskell, we are likely to see kind polymorphism, if at all, in the form of type classes whose type parameters can be of different, perhaps of all kinds.) Frederik, for the time being I propose to look into TH code for deriving Tyepable/Data instances and to make it fit for your purposes. There are several versions of Ulf Norell's code around. You may also use SYB3 with the TH code that readily comes with it. Thanks for bringing this up. Regards, Ralf > -Original Message- > From: Frederik Eaton [mailto:[EMAIL PROTECTED] > Sent: Sunday, September 18, 2005 7:50 PM > To: Ralf Lammel > Cc: haskell-cafe@haskell.org > Subject: Re: [Haskell-cafe] generics question, logical variables > > Hi Ralf, > > I'm revisiting this project and just have another question. The story > seems to be that GHC cannot derive Typeable1, or Typeable when > Typeable1 is available - so anyone who wants to use ext1Q must define > special instances for all of the datatypes they use, is this correct? > Will this change soon? > > Aside from that, your 'idify' in PseudoFmap2 certainly seems to have > the correct type for this application. However, the absence of > automatic derivation is somewhat of an impediment. > > Thanks for your help. > > Frederik > > On Tue, Aug 30, 2005 at 02:25:08PM -0700, Ralf Lammel wrote: > > Frederik, > > > > > As for your code example, it looks very interesting, but are you > > > saying that this could turn into an extension of the Data.Generics > > > library, or that this is something I could be implementing in terms of > > > what's already there? > > > > The posted code works with GHC 6.4 (SYB2) intentionally and actually. I > > have attached another attempt (again GHC 6.4, based on SYB2) which might > > be more useful for your purposes, and it may be useful in general, in > > fact. > > > > What I defined this time is a "certainty-improving" function: > > > > idify :: (Typeable1 f, Monad m, Data (a f), Data (a Id)) > > => (forall a. f a -> m a) -> a f -> m (a Id) > > > > That is, the function "idify get" takes a value whose type is > > parameterized in a type constructor f (such as Maybe or IORef), and the > > function attempts to establish Id instead of f on the basis of
Re: [Haskell-cafe] How to debug GHC
> > It could be a bug - can you reduce the example and report it? > > > > GHC's profiler tries to overlay a lexical call graph on to the dynamic > > execution of the program. It does this more or less in the way you > > described before: every function gets an extra argument describing the > > call context. However, there are some tricky areas: notably CAFs. We > > don't as yet have a principled description of the mechanism, and I know > > of various cases where odd results are obtained with the current system. > > Also, the optimiser has to be careful not to change the shape of the > > call graph, and I suspect there are cases where it goes wrong. > > I see. Well, I'm afraid I've lost the example, but I'll keep my eyes > open in case it happens again. It's good to know what the correct > behavior is supposed to be. While I was finishing a project for somebody I ran into this problem again, as well as some other bugs, and made several copies of the code so that the problems could be reproduced. In addition to the stack trace problems, I found: (1) a problem where output freezes when it is being piped through 'tee' and the user presses ^S and then ^Q and (2) an issue where a "trace" statement is not being printed correctly by ghc (but is being printed correctly by runghc). However, I don't have time to reduce these to minimal test cases. Do you want to look at them anyway? Frederik -- http://ofb.net/~frederik/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] generics question, logical variables
Hi Ralf, I'm revisiting this project and just have another question. The story seems to be that GHC cannot derive Typeable1, or Typeable when Typeable1 is available - so anyone who wants to use ext1Q must define special instances for all of the datatypes they use, is this correct? Will this change soon? Aside from that, your 'idify' in PseudoFmap2 certainly seems to have the correct type for this application. However, the absence of automatic derivation is somewhat of an impediment. Thanks for your help. Frederik On Tue, Aug 30, 2005 at 02:25:08PM -0700, Ralf Lammel wrote: > Frederik, > > > As for your code example, it looks very interesting, but are you > > saying that this could turn into an extension of the Data.Generics > > library, or that this is something I could be implementing in terms of > > what's already there? > > The posted code works with GHC 6.4 (SYB2) intentionally and actually. I > have attached another attempt (again GHC 6.4, based on SYB2) which might > be more useful for your purposes, and it may be useful in general, in > fact. > > What I defined this time is a "certainty-improving" function: > > idify :: (Typeable1 f, Monad m, Data (a f), Data (a Id)) > => (forall a. f a -> m a) -> a f -> m (a Id) > > That is, the function "idify get" takes a value whose type is > parameterized in a type constructor f (such as Maybe or IORef), and the > function attempts to establish Id instead of f on the basis of the > function argument "get". > > > What is the 'a' parameter for in "force"? > > > > force :: ( Data (t Maybe a) > > , Data (t Id a) > > , Term t Maybe a > > , Term t Id a > > ) => t Maybe a -> t Id a > > The previous attempt was a more parameterized blow than required in your > case. (I was guessing about what "typed logical variables" could mean. > I was assuming that you would need some extra layer of embedding types > on top of the Haskell term types. Looking at your code, this was not the > case.) > > > For the part which I asked for help with, to get around my trouble > > with generics, I defined a class GenFunctor and an example instance. > > The intent is that generics should be able to provide this > > functionality automatically later on, but you can see what the > > functionality is. > > Let's look at the type of your GenFunctor: > > class GenFunctor f where > gfmapM :: (Monad m, FunctorM b) => (forall x . a x -> m (b x)) -> f > a -> m (f b) > > This type can be seen as a more relaxed version of the idify operation > above. That is, idify fixes GenFunctor's b to Id. The particular > encoding of idify (attached) takes advantage of this restriction. I > wonder whether I should bother. (Exercise for reader :-)) > > > However, I am stuck on something else, the program doesn't typecheck > > because of use of another function I defined, 'cast1'. Maybe you can > > take a look. I had thought that I would be able to write a generic > > 'unify' but I get the error: > > > > GenLogVar.hs:82:19: > > Ambiguous type variable `a' in the constraint: > > `Data a' arising from use of `cast1' at GenLogVar.hs:82:19-23 > > Probable fix: add a type signature that fixes these type > variable(s) > > > > This is because I need to do something special when I encounter a > > "Var" variable in unification, but the compiler seems to not like the > > fact that the type argument of the Var data type is not known. > > Please try to avoid new cast operations at all costs. :-) > Your code can be arranged as follows: > > (i) Use extQ1 to dispatch to a special case for "Var x" for the first > argument. (ii) In this special case, use again ext1Q to dispatch to a > special case for "Var y" for the second argument. (iii) At this point, > *cast* the variable value of *one* variable to the type of the other. > > So the problem with your code, as it stands, is that the target type of > cast is ambiguous because you cast *both* arguments. The insight is to > make the cast asymmetric. Then, not even polymorphism is in our way. > > Interesting stuff! > > Ralf > -- http://ofb.net/~frederik/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Eq Type Class: Overloading (==)
On 2005-09-18, Tom Hawkins <[EMAIL PROTECTED]> wrote: > I like the idea of supertyping, but wouldn't that only allow you to > alter identifiers that were already classified? Correct. > What about functions in the Prelude that don't belong to a type class? Nope. -- Aaron Denney -><- ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Re[2]: [Haskell-cafe] Eq Type Class: Overloading (==)
On Sat, Sep 17, 2005 at 12:36:06PM -0700, Jason Dagit wrote: > > On Sep 17, 2005, at 1:43 AM, Bulat Ziganshin wrote: > > > >about making Bool a class - it is the same issue as making > >head/map/... belonging to some Collection class. we need to change > >standard Prelude or add to Haskell "supertyping" mechanism, proposed > >by John Meacham, as i remember > > A link to supertyping can be found here: > http://repetae.net/john/recent/out/supertyping.html > > After reading that, I wonder why it's not implemented. It seems like > a wonderfully useful idea. I view it as a way to add things back to > the language which should have been there to begin with, but which > the language designers left out for various reasons (such as lack of > time, interest or possibly even oversight). I actually have some misgivings about the design I stated there and would have some tweaks I would like to do before it was actually implemented, but I definitly think we need more flexible ways to deal with class hierachies (in some form). my main concern is that class Eq a => Ord a where class Ord a <= Eq a where are not fully symmetric. the second lets you just declare things as Ord without worrying about Eq, the first doesn't. I think these issues can be worked out once a concrete implementation is being worked on, which I hope to do for jhc. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Eq Type Class: Overloading (==)
On Fri, Sep 16, 2005 at 11:14:14PM -0700, Jason Dagit wrote: > This reminds me that several times now I've wished that Bool was some > sort of interface instead of a type. Perhaps Bool could be a type > class? I also wish that "if" were a function, but that's probably > just the lisper in me speaking. Something like: See my Boolean.Algebra module. it lets you declare types to be boolean algebras (or lift an arbitrary type to such an algebra) and provides a lot of useful functions on them. although, it sometimes feels like it should be a general lattice class. http://repetae.net/john/recent/out/Boolean.html darcs repo: http://repetae.net/john/repos/Boolean some examples of where I have used this are. in ginsu you can have filters to choose which messages to see. I just created the basic regex filter and lifted it to a full boolean alegbra on them with Boolean.Boolean. In jhc I accumulate various properties of programs with generic routines that accumulate arbitrary types of class boolean. "fuzzy" booleans implemented as doubles have found their way into some projects. and some other places... John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Eq Type Class: Overloading (==)
On Sunday 18 September 2005 07:59 am, Tom Hawkins wrote: > Aaron Denney wrote: > > On 2005-09-17, Jason Dagit <[EMAIL PROTECTED]> wrote: > >>A link to supertyping can be found here: > >>http://repetae.net/john/recent/out/supertyping.html > >> > >>After reading that, I wonder why it's not implemented. > > > > Not enough people calling for it. > > > >>It seems like a wonderfully useful idea. > > > > It is. It would be terribly useful for those trying to prototype a > > new Prelude, and clean up the mathematical structures. > > I like the idea of supertyping, but wouldn't that only allow you to > alter identifiers that were already classified? What about functions in > the Prelude that don't belong to a type class? > > For instance, I have a datatype that needs an append-like operation, yet > it appears (++) is reserved only for lists. > > I recently switched to Haskell from OCaml because I thought type classes > may solve one of my problems. I'm building an embedded language, which > has a lot of the basic operations. In OCaml I was forced to invent all > sort of obscure operator names for the embedded language so as not to > collide with the standard library. > > But with Haskell's Num class, I have been able to reuse (+), (-), and > (*). However, (==) and (++) are still sticking points. My general > impression of Haskell is good, though it seems you're somewhat locked-in > by how the upper levels of the class hierarchy are defined in the > Prelude, or when the Prelude does not type class generic operator names > such as (++). > > Again, I just stared programming Haskell. Please let me know if I'm > missing something. One possible solution for DSLs is to import the Prelude qualified, or with a hiding clause. That allows you to redefine most of the symbols in the Prelude, but still use the Prelude ones if needed. (==) is still a little special because the Prelude (==) is used for some desugaring steps. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Eq Type Class: Overloading (==)
Aaron Denney wrote: On 2005-09-17, Jason Dagit <[EMAIL PROTECTED]> wrote: A link to supertyping can be found here: http://repetae.net/john/recent/out/supertyping.html After reading that, I wonder why it's not implemented. Not enough people calling for it. It seems like a wonderfully useful idea. It is. It would be terribly useful for those trying to prototype a new Prelude, and clean up the mathematical structures. I like the idea of supertyping, but wouldn't that only allow you to alter identifiers that were already classified? What about functions in the Prelude that don't belong to a type class? For instance, I have a datatype that needs an append-like operation, yet it appears (++) is reserved only for lists. I recently switched to Haskell from OCaml because I thought type classes may solve one of my problems. I'm building an embedded language, which has a lot of the basic operations. In OCaml I was forced to invent all sort of obscure operator names for the embedded language so as not to collide with the standard library. But with Haskell's Num class, I have been able to reuse (+), (-), and (*). However, (==) and (++) are still sticking points. My general impression of Haskell is good, though it seems you're somewhat locked-in by how the upper levels of the class hierarchy are defined in the Prelude, or when the Prelude does not type class generic operator names such as (++). Again, I just stared programming Haskell. Please let me know if I'm missing something. Thanks! -Tom ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Newbie syntax question
> > map (foo 5) my_list_of_lists_of_doubles > 1. map (flip foo 5) my_list_of_lists_of_doubles > 2. map (`foo` 5) my_list_of_lists_of_doubles > 3. map (\x->foo x 5) my_list_of_lists_of_doubles > 4. [foo x 5 | x <- my_list_of_lists_of_doubles] well, i've followed this discussion a while, but i did not see that solution i used for years. (i like solution 2, never thought of it before.) my solution is a variant of 1, that makes the reading a little bit easier -- at least to me. 5. map (foo `flip` 5) my_list_of_lists_of_doubles the `flip` shows the position behind foo, where to put the parameter. its a pitty that it only works if there is only one parameter behind `flip`. so, with abcd :: a->b->c->d->x abcd a b `flip` d :: c->x works, but abcd a `flip` c d :: b->x does not. experimenting with Data.Arrow, it could look like: (abcd a >>> ($ c) >>> ($ d)) :: b->x or with a flip-arrow combination: (abcd a `flip` c) >>> ($ d) :: b->x so, instead of hacking with arrows on it, i prefer solutions 3 and 4 whenever 5 does not work. - marc ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Newbie syntax question
Hi, Andre, > map (foo 5) my_list_of_lists_of_doubles > > ...But how to do that (if possible) when I >invert the parameters list ?! Let me add one more solution, and then summarize: The problem disapears if you use a list comprehension instead of map: [foo x 5 | x <- my_list_of_lists_of_doubles] List comprehensions are funny. Sometimes, they are powerful, consise, and crystal clear. Other times they can seem wordy and confusing. In this case it works well. OK, so the four solutions that have been suggested are: 1. map (flip foo 5) my_list_of_lists_of_doubles 2. map (`foo` 5) my_list_of_lists_of_doubles 3. map (\x->foo x 5) my_list_of_lists_of_doubles 4. [foo x 5 | x <- my_list_of_lists_of_doubles] (1) and (2) are closest to what you originally wanted to write. They do not neatly generalize beyond the second parameter. (3) is more general - but a little less clear. (4) is the most different from your original idea. In a certain sense, it is even more general than (3). In this case, it is also simple and clear - though you may not always be so lucky. BTW - great question! Regards, Yitz ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe