Is there a way to find out the type inferred for a local function inside another function? :)

On Thursday 07 April 2011 21:52:29, KC wrote:
There are probably better ways, but: module Infer where foo :: Num a => [a] -> a foo = go 0 0 where go :: b go i s (x:xs) = go (i+1) (s+i*x) xs go _ s _ = s $ ghc Infer [1 of 1] Compiling Infer ( Infer.hs, Infer.o ) Infer.hs:7:5: Could not deduce (b ~ (a0 -> a0 -> [a0] -> a0)) from the context (Num a) bound by the type signature for foo :: Num a => [a] -> a at Infer.hs:(4,1)-(8,16) `b' is a rigid type variable bound by the type signature for go :: b at Infer.hs:7:5 The equation(s) for `go' have three arguments, but its type `b' has none In an equation for `foo': foo = go 0 0 where go :: b go i s (x : xs) = go (i + 1) (s + i * x) xs go _ s _ = s sort of does it.

AFAIK there is no way to do that, thouhg scion[1] may offer it. Personally I develop more complex local functions at the top-level, and once I'm happy with it I perform some re-factoring and move it in. /M [1]: https://github.com/nominolo/scion/blob/master/README.markdown -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus@therning.org jabber: magnus@therning.org twitter: magthe http://therning.org/magnus

Magnus Therning schrieb:
AFAIK there is no way to do that, thouhg scion[1] may offer it.
Personally I develop more complex local functions at the top-level, and once I'm happy with it I perform some re-factoring and move it in.
I would not write large local functions at all. I would leave them top-level but do not export them. This also allows to test them from GHCi.

On Fri, Apr 8, 2011 at 5:24 AM, Henning Thielemann
Magnus Therning schrieb:
AFAIK there is no way to do that, thouhg scion[1] may offer it.
Personally I develop more complex local functions at the top-level, and once I'm happy with it I perform some re-factoring and move it in.
I would not write large local functions at all. I would leave them top-level but do not export them. This also allows to test them from GHCi.
Agreed, I do this as well. However, I occasionally would like to do a "reverse infer", for example: bigFunction = ... helper x y z helper = undefined Now I want to find out what type 'helper' should be in order that it typecheck within bigFunction. Obviously 'undefined's type 'a' trivially satisfies that, so it can't be the most general possible type because that's always just 'a'. Currently what I do is declare a signature for helper, and then if it gets a type error try to figure out how to fix it. It's usually not very hard, but it would be slick to have the signature filled in automatically.

Currently what I do is declare a signature for helper, and then if it gets a type error try to figure out how to fix it. It's usually not very hard, but it would be slick to have the signature filled in automatically.
Try ghc-mod on Hackage if you are an Emacs user. If GHC can guess the signature of helper function, haskell-mode with ghc-mod automatically hilights the function. Typing C-cC-t inserts the guessed signature. http://www.mew.org/~kazu/proj/ghc-mod/en/ --Kazu

I made a mistake. Use M-t instead of C-cC-t.
Currently what I do is declare a signature for helper, and then if it gets a type error try to figure out how to fix it. It's usually not very hard, but it would be slick to have the signature filled in automatically.
Try ghc-mod on Hackage if you are an Emacs user.
If GHC can guess the signature of helper function, haskell-mode with ghc-mod automatically hilights the function. Typing C-cC-t inserts the guessed signature.
http://www.mew.org/~kazu/proj/ghc-mod/en/
--Kazu

Agda's concept of holes seems perfect for this. Does Haskell have
anything similar?
On Fri, Apr 8, 2011 at 9:50 PM, Kazu Yamamoto
I made a mistake. Use M-t instead of C-cC-t.
Currently what I do is declare a signature for helper, and then if it gets a type error try to figure out how to fix it. It's usually not very hard, but it would be slick to have the signature filled in automatically.
Try ghc-mod on Hackage if you are an Emacs user.
If GHC can guess the signature of helper function, haskell-mode with ghc-mod automatically hilights the function. Typing C-cC-t inserts the guessed signature.
http://www.mew.org/~kazu/proj/ghc-mod/en/
--Kazu
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, Apr 8, 2011 at 13:24, Henning Thielemann
Magnus Therning schrieb:
AFAIK there is no way to do that, thouhg scion[1] may offer it.
Personally I develop more complex local functions at the top-level, and once I'm happy with it I perform some re-factoring and move it in.
I would not write large local functions at all. I would leave them top-level but do not export them. This also allows to test them from GHCi.
Indeed, but complex /= large :-) /M -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus@therning.org jabber: magnus@therning.org twitter: magthe http://therning.org/magnus

On 4/8/11 8:24 AM, Henning Thielemann wrote:
Magnus Therning schrieb:
AFAIK there is no way to do that, thouhg scion[1] may offer it.
Personally I develop more complex local functions at the top-level, and once I'm happy with it I perform some re-factoring and move it in.
I would not write large local functions at all. I would leave them top-level but do not export them. This also allows to test them from GHCi.
The downside to this is when you want to use the worker/wrapper transform in order to capture some local variables for a recursive function, instead of passing them through the recursion. -- Live well, ~wren

I would not write large local functions at all. I would leave them top-level but do not export them. This also allows to test them from GHCi.
The downside to this is when you want to use the worker/wrapper transform in order to capture some local variables for a recursive function, instead of passing them through the recursion.
I do this a lot too, but it doesn't mean you have to have large functions. The type of the worker is usually pretty trivially derived from the type of wrapper, e.g. wrapper :: A -> B -> C -> D wrapper a b = go 0 where go n c = .... I've had a couple of cases with large functions with large numbers of parameters that have a complicated recursion pattern and those are indeed hard to factor into top level functions because each internal definition uses a random assortment of variables (not necessarily worker/wrapper either). I suppose a refactoring editor could pull inner definitions up to the top level and push them back down, but hopefully those hairball functions are not common.
participants (9)
-
Daniel Fischer
-
Evan Laforge
-
Henning Thielemann
-
Henning Thielemann
-
Kazu Yamamoto
-
KC
-
Lyndon Maydwell
-
Magnus Therning
-
wren ng thornton