Displaying infered type signature of 'offside' functions

Hi, I like the strong static type system of Haskell for various reasons. One reason is, that it makes easier to understand new code. I.e. when I read code I type ':t foo' in ghci/hugs from time to time, to check my own idea of the type signature, if it is not included in the source code. Well, ':t ' doesn't work withwith non-top-level/local functions (or does it?). Thus I searched for a way to get this information for functions, which are defined offside (of the main indentation level). So, what tools do you use to get the inferred type signature of local functions? I first looked at the GHC-API, but I found this comment in http://darcs.haskell.org/ghc/compiler/main/GHC.hs : - NOTE: -- - things that aren't in the output of the typechecker right now: [..] -- - type signatures Hm, is this comment in sync with the current GHC source? Then I looked at the ghc options. '-ddump-types' only dumps the signatures of global functions ... But '-ddump-tc' includes type signatures of offside defined functions. I.e. something like ghc -ddump-tc Foo.lhs 2>&1 \ | awk '/^[A-Z].+lhs/, ! // { print $0; }' \ | awk '/ :: / , /\[\]/ { if (!($0 ~ /\[\]/)) print $0; }' \ | less does the trick. But as the haskell/ghc wiki mentions, the -ddump-* output is optimized for human reading and not for some kind of 'automatic use'. For automatic use one should look at the GHC-API ... Well, I mention this, because I would like to integrate some lookup feature (for type signatures) into vim (if it doesn't exist yet). Best regards Georg Sauthoff

Thus I searched for a way to get this information for functions, which are defined offside (of the main indentation level).
So, what tools do you use to get the inferred type signature of local functions?
i tend to do that by hand: if i write f .. = e where ..defs.. as f .. = rhs where rhs = e .. defs .. i can replace rhs with anything in scope within f, and test or type it in ghci. the trouble, of course, are the other calls to f, which don't like the change in type. so instead i have to take f out of production use, somewhat like this f .. = undefined f' .. = rhs where rhs = e[f'/f] .. defs[f'/f] .. and use f' for testing and typechecking.. so, if you get your alternative to work, i'd be interested to add that to my own vim scripts as well!-) it seems one needs to compile the source before one can use -ddump-tc?
But '-ddump-tc' includes type signatures of offside defined functions.
I.e. something like
ghc -ddump-tc Foo.lhs 2>&1 \ | awk '/^[A-Z].+lhs/, ! // { print $0; }' \ | awk '/ :: / , /\[\]/ { if (!($0 ~ /\[\]/)) print $0; }' \ | less
does the trick.
But as the haskell/ghc wiki mentions, the -ddump-* output is optimized for human reading and not for some kind of 'automatic use'. For automatic use one should look at the GHC-API ...
Well, I mention this, because I would like to integrate some lookup feature (for type signatures) into vim (if it doesn't exist yet).
GHC-API would be the preferred solution, but editor bindings traditionally have to interpret all kinds of output not intended for anyone's consumption. you can certainly store the output, do substitutions, and associate types with identifiers via associative arrays, so you need only one call to get all local types, if you can extract and identify the information. claus

On 28/04/07, Georg Sauthoff
Well, I mention this, because I would like to integrate some lookup feature (for type signatures) into vim (if it doesn't exist yet).
It's worth pointing out that Emacs's haskell-mode already has this. For anyone that uses the major mode but hasn't heard of the inf-haskell features: C-c C-t inferior-haskell-type: looks up a type of the function under point, built-in or user-defined. C-c C-i inferior-haskell-info: looks up the info, à la GHCi :info, of the identifer under point, built-in or user-defined. C-c M-. inferor-haskell-find-definition: jumps to the definition of the function, class or datatype etc. under point. See the Haskell wiki page [1] for more information. [1]: http://haskell.org/haskellwiki/Haskell_mode_for_Emacs#inf-haskell.el:_the_be... -- -David House, dmhouse@gmail.com

On 29/04/07, David House
It's worth pointing out that Emacs's haskell-mode already has this. For anyone that uses the major mode but hasn't heard of the inf-haskell features:
I did forget to mention that this won't help with your 'offside' functions, though. -- -David House, dmhouse@gmail.com

On 28/04/07, Georg Sauthoff
wrote: Well, I mention this, because I would like to integrate some lookup feature (for type signatures) into vim (if it doesn't exist yet).
It's worth pointing out that Emacs's haskell-mode already has this.
as do many Vim Haskell modes. for instance, in my own, there are _t : show type for id under cursor _T : add type declaration for id under cursor before current line _si : show info for id under cursor CTRL-] : jump to definition of id under cursor '_t' and '_T' use (cached) output from GHCi :browse for the current and imported modules, '_si' calls GHCi :info, CTRL-] uses the tags file generated by 'ghc -e :ctags <current>' (which is mapped to '_ct'). see http://www.cs.kent.ac.uk/people/staff/cr3/toolbox/haskell/Vim/ for more info, a tour, and the scripts.
I did forget to mention that this won't help with your 'offside' functions, though.
that, indeed, is the point. if it is reasonably easy to get that information, without internal identifiers or non-source constructs, and with correct associations to source code positions, it would be a useful addition to editor bindings. it would perhaps be nice to have a wiki page collecting Haskell IDE features that have been implemented in at least one of the many tools, so that everybody can try to implement a similar feature set for their own editor/ide? there are features that depend on individual preferences, such as indentation, and there are obvious features that everybody wants, such as those above, but often, someone somewhere hacks up a little trick that makes Haskell hacking life a lot easier. here is a near trivial example from my vimrc file (not even Haskell- specific): map ,{ c{}<esc>P% map ,( c()<esc>P% map ,[ c[]<esc>P% this allows me to insert parens by highlighting the part to be enclosed (*). similarly, the emacs modes have a command to align patterns in the middle of adjacent lines, such as '=', '::', which is different from indent, and sounds potentially quite useful, to align multiple equations and their type declaration, so i've started to reproduce that for vim. claus (*) ',(' is mapped to: replace (c) highlighted, insert '()', escape to command mode (<esc>), paste cut buffer before current pos (P), jump to matching paren (%). so i just highlight an expr and hit ',(' to put it in parens, or ',[' to wrap it into a list, etc.

This looks like a good place to ask a question that's been bugging me for a bit: I've had cases in my own code where I can't seem to create a type annotation for an "inner" declaration that the type-checker likes. Here's a toy example: In the following code:
applyfunc :: (a -> b -> c) -> a -> b -> c applyfunc f x y = doit y where doit = f x
What type annotation can I successfully apply to the function "doit"?
Thanks,
Antoine
On 4/29/07, Claus Reinke
On 28/04/07, Georg Sauthoff
wrote: Well, I mention this, because I would like to integrate some lookup feature (for type signatures) into vim (if it doesn't exist yet).
It's worth pointing out that Emacs's haskell-mode already has this.
as do many Vim Haskell modes. for instance, in my own, there are
_t : show type for id under cursor _T : add type declaration for id under cursor before current line _si : show info for id under cursor CTRL-] : jump to definition of id under cursor
'_t' and '_T' use (cached) output from GHCi :browse for the current and imported modules, '_si' calls GHCi :info, CTRL-] uses the tags file generated by 'ghc -e :ctags <current>' (which is mapped to '_ct').
see http://www.cs.kent.ac.uk/people/staff/cr3/toolbox/haskell/Vim/ for more info, a tour, and the scripts.
I did forget to mention that this won't help with your 'offside' functions, though.
that, indeed, is the point. if it is reasonably easy to get that information, without internal identifiers or non-source constructs, and with correct associations to source code positions, it would be a useful addition to editor bindings.
it would perhaps be nice to have a wiki page collecting Haskell IDE features that have been implemented in at least one of the many tools, so that everybody can try to implement a similar feature set for their own editor/ide?
there are features that depend on individual preferences, such as indentation, and there are obvious features that everybody wants, such as those above, but often, someone somewhere hacks up a little trick that makes Haskell hacking life a lot easier.
here is a near trivial example from my vimrc file (not even Haskell- specific):
map ,{ c{}<esc>P% map ,( c()<esc>P% map ,[ c[]<esc>P%
this allows me to insert parens by highlighting the part to be enclosed (*).
similarly, the emacs modes have a command to align patterns in the middle of adjacent lines, such as '=', '::', which is different from indent, and sounds potentially quite useful, to align multiple equations and their type declaration, so i've started to reproduce that for vim.
claus
(*) ',(' is mapped to: replace (c) highlighted, insert '()', escape to command mode (<esc>), paste cut buffer before current pos (P), jump to matching paren (%). so i just highlight an expr and hit ',(' to put it in parens, or ',[' to wrap it into a list, etc.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, Apr 29, 2007 at 07:03:32PM -0500, Antoine Latter wrote:
This looks like a good place to ask a question that's been bugging me for a bit:
I've had cases in my own code where I can't seem to create a type annotation for an "inner" declaration that the type-checker likes. Here's a toy example:
In the following code:
applyfunc :: (a -> b -> c) -> a -> b -> c applyfunc f x y = doit y where doit = f x
What type annotation can I successfully apply to the function "doit"?
There isn't one, plain and simple. However, if you allow GHC extensions, you can: {-# Language ScopedTypeVariables #-} applyfunc :: forall a b c . (a -> b -> c) -> a -> b -> c applyfunc f x y = doit y where doit :: b -> c doit = f x The 'forall' serves no other purpose than to deliberately break haskell 98 compatibility. Stefan

| I like the strong static type system of Haskell for various | reasons. One reason is, that it makes easier to understand new | code. I.e. when I read code I type ':t foo' in ghci/hugs from | time to time, to check my own idea of the type signature, if it | is not included in the source code. The principal difficulties here are to do with "what do we want" rather the implementation challenges. 1. Should the compiler print the type of every declaration? Should GHCi allow you to ask the type of a local decl? 2. How should the variables be identified? There may be many local bindings for 'f', so you can't say just ":t f". Ditto if dumping all local bindings. 3. Do you want all locally-bound variables (including those bound by lambda or case), or just letrec/where bound ones? I think 'all', myself, but there are a lot of them. 4. (This is the trickiest one.) The type of a function may mention type variables bound further out. Consider f :: [a] -> Int f xs = let v = head xs in ... The type of 'v' is simply 'a'. Not 'forall a. a', but rather 'if xs:[a] then *that* a!' In general there may also be existential type variables bound by an enclosing pattern match too. So it's not easy to see how to report v's type. In general there is no type signature for f, which only makes matters worse, since there is no name to use for the in-scope type variable. These are all user-interface issues. If some people would like to thrash out a design, and put it on the Wiki, I think there is a good chance that someone (possibly even me) would implement it. Simon

Simon Peyton-Jones wrote:
| I like the strong static type system of Haskell for various | reasons. One reason is, that it makes easier to understand new | code. I.e. when I read code I type ':t foo' in ghci/hugs from | time to time, to check my own idea of the type signature, if it | is not included in the source code.
The principal difficulties here are to do with "what do we want" rather the implementation challenges.
1. Should the compiler print the type of every declaration? Should GHCi allow you to ask the type of a local decl?
IMO, ghci should definitely allow you to ask. This comes up for me every time that I write any haskell code (and in general I end up hoisting local definitions to the top level, which is a real pain if there is local scope, data or type, to hoist with it).
2. How should the variables be identified? There may be many local bindings for 'f', so you can't say just ":t f". Ditto if dumping all local bindings.
I think this is a hard question. I was imagining some kind of hierarchical system like foo.f, in the case that f is locally defined inside foo. (Yes I know we can't easily use '.' for that). There might be might be multiple fs inside the definition of foo; indeed there might even be multiple fs nested inside each other. I suspect the happy medium, rather than a formal way of accessing every possible position, is a contextually intelligent system which allows the user to disambiguate. So 'foo.f' will show all the fs inside foo if there are, say, fewer than 5, or otherwise ask for more guidance.
3. Do you want all locally-bound variables (including those bound by lambda or case), or just letrec/where bound ones? I think 'all', myself, but there are a lot of them.
All, I think. (It's very common in multiple cases for the same name to be used repeatedly at the same type; this could be conveniently indicated concisely, perhaps).
4. (This is the trickiest one.) The type of a function may mention type variables bound further out. Consider f :: [a] -> Int f xs = let v = head xs in ...
The type of 'v' is simply 'a'. Not 'forall a. a', but rather 'if xs:[a] then *that* a!' In general there may also be existential type variables bound by an enclosing pattern match too.
I think you're going to have to give the type context, in such cases. (a :: *) |- v : a ... possibly with some way to access information about where the binding site for 'a' is.
These are all user-interface issues. If some people would like to thrash out a design, and put it on the Wiki, I think there is a good chance that someone (possibly even me) would implement it
That would be a good idea; my comments above do not a design make though. Can anyone else elaborate further? Jules

Jules Bean
Simon Peyton-Jones wrote: The principal difficulties here are to do with "what do we want" rather the implementation challenges.
1. Should the compiler print the type of every declaration? Should GHCi allow you to ask the type of a local decl?
IMO, ghci should definitely allow you to ask. This comes up for me every time that I write any haskell code (and in general I end up hoisting local definitions to the top level, which is a real pain if there is local scope, data or type, to hoist with it).
2. How should the variables be identified? There may be many local bindings for 'f', so you can't say just ":t f". Ditto if dumping all local bindings.
I think this is a hard question. I was imagining some kind of hierarchical system like foo.f, in the case that f is locally defined inside foo. (Yes I know we can't easily use '.' for that). There might be might be multiple fs inside the definition of foo; indeed there might even be multiple fs nested inside each other.
I just wanted to contribute a PRACTICAL TRICK I use: * If the local definition is a pattern binding f = ... then I just add f :: Ordering * If the local definition is a, say binary, function binding f p1 p2 = ... then I just add f :: Float -> Double -> Ordering (Type does not matter for the number of function arrows you need to put; only the syntactic arity of the bindings matters here.) This relies on the fact that the types Float, Double, and Ordering very rarely occur in my code --- pick your own. Now the compiler gives you wonderful error messages ``cannot match type `x y z' against Ordering'' --- so you replace ``Ordering'' with ``x y z''. If there are type variables in ``x y z'' that come from the context, take care that you have {-# LANGUAGE ScopedTypeVariables #-} at the beginning of your module (after the {-# OPTIONS ...#-} line, which should, as a matter of style, NOT contain -fglasgow-exts ) and the necessary ``forall ty1 ty2 ...'' in front of your the type in the type signature of the enclosing definition. At the cost of a re-compilation, this works wonderfully for me, and is much less painful than hoisting AND exporting local definitions. But even I still have some wishes open: * It would be nice if this worked inside the do-notation, too: do x :: Ordering x <- m (This is curently a syntax error.) * It would be nice if {-# LANGUAGE ScopedTypeVariables #-} brought in no other extensions, and if GHC would recommend the appropriate LANGUAGE pragmas instead of -fglasgow-exts when it determines that the user might have wanted some extension. (What is the right Language.Extension for GADTs?) Wolfram

On 2 May 2007 16:16:57 -0000, kahl@cas.mcmaster.ca
* It would be nice if this worked inside the do-notation, too:
do x :: Ordering x <- m
(This is curently a syntax error.)
I think the following works with -fglasgow-exts: do (x :: Ordering) <- m -- -David House, dmhouse@gmail.com

kahl@cas.mcmaster.ca wrote:
Jules Bean
wrote, concerning the problem of getting at the types of local definitions: Simon Peyton-Jones wrote: The principal difficulties here are to do with "what do we want" rather the implementation challenges.
1. Should the compiler print the type of every declaration? Should GHCi allow you to ask the type of a local decl?
IMO, ghci should definitely allow you to ask. This comes up for me every time that I write any haskell code (and in general I end up hoisting local definitions to the top level, which is a real pain if there is local scope, data or type, to hoist with it).
2. How should the variables be identified? There may be many local bindings for 'f', so you can't say just ":t f". Ditto if dumping all local bindings.
I think this is a hard question. I was imagining some kind of hierarchical system like foo.f, in the case that f is locally defined inside foo. (Yes I know we can't easily use '.' for that). There might be might be multiple fs inside the definition of foo; indeed there might even be multiple fs nested inside each other.
I just wanted to contribute a PRACTICAL TRICK I use:
* If the local definition is a pattern binding
f = ...
then I just add
f :: Ordering
* If the local definition is a, say binary, function binding
f p1 p2 = ...
then I just add
f :: Float -> Double -> Ordering
(Type does not matter for the number of function arrows you need to put; only the syntactic arity of the bindings matters here.)
This relies on the fact that the types Float, Double, and Ordering very rarely occur in my code --- pick your own.
Why not just declare a type you don't use?

On Wed, May 02, 2007 at 04:16:57PM -0000, kahl@cas.mcmaster.ca wrote:
Now the compiler gives you wonderful error messages ``cannot match type `x y z' against Ordering'' --- so you replace ``Ordering'' with ``x y z''.
You could just use a rigid type variable: foo :: a foo = ...
(What is the right Language.Extension for GADTs?)
There is none. Stefan

Simon Peyton-Jones
The principal difficulties here are to do with "what do we want" rather the implementation challenges.
yes, I thought that too (I mean a haskell compiler have to deal with 'the' wanted information already for typechecking purposes etc.).
1. Should the compiler print the type of every declaration?
With -tdump-types, yes.
Should GHCi allow you to ask the type of a local decl?
Yes.
2. How should the variables be identified? There may be many local bindings for 'f', so you can't say just ":t f". Ditto if dumping all local bindings.
Well, for where-bound ones at least I would consider something like :t f$g$h or :t f.g.h as a useable command to identify this h: f ... = .. where g ... = ... where h ... = ... If the hierachy is not unique, :t could print all matches, and if the user wants to be more specific, he could issue something like :t f#2.h for the last h in someting something like f ... = ... where h ... = ... f ... = ... where h .. = ... Well, something like :t f.g.* would be nice, too, where * works like in 'pattern globbing' (i.e. matching all decls local to f.g).
3. Do you want all locally-bound variables (including those bound by lambda or case), or just letrec/where bound ones? I think 'all', myself, but there are a lot of them.
I just thought about where/let bound ones. But I am not sure ;)
4. (This is the trickiest one.) The type of a function may mention type variables bound further out. Consider f :: [a] -> Int f xs = let v = head xs in ...
Have to think about it.
These are all user-interface issues. If some people would like to thrash out a design, and put it on the Wiki, I think there is a good chance that someone (possibly even me) would implement it.
Sounds great! I will wait a few days, if someone extends this thread and then put the ideas from this thread on a wiki-page and post the link (if not someone else do it first). Best regards Georg Sauthoff
participants (9)
-
Antoine Latter
-
Claus Reinke
-
David House
-
Derek Elkins
-
Georg Sauthoff
-
Jules Bean
-
kahl@cas.mcmaster.ca
-
Simon Peyton-Jones
-
Stefan O'Rear