
Can someone explain what's wrong here? What is the code below _really_ saying, vs what I meant? I don't understand the error messages yet. == input == module Main ( main ) where solve n src dest tmp = do solve (n-1) src tmp -- line 6 solve 1 src dest tmp solve (n-1) tmp dest -- line 8 solve 1 src dest _ = putStrLn "move a disk from " ++ src ++ " to " ++ dest -- line 11 main = do putStrLn "Towers of Hanoi problem" solve 5 "A" "B" "C" == output == Prelude> :reload [1 of 1] Compiling Main ( towers1.hs, interpreted ) Failed, modules loaded: none. Prelude> towers1.hs:6:8: Couldn't match expected type `[a0]' with actual type `[Char] -> [Char]' In the return type of a call of `solve' Probable cause: `solve' is applied to too few arguments In a stmt of a 'do' block: solve (n - 1) src tmp In the expression: do { solve (n - 1) src tmp; solve 1 src dest tmp; solve (n - 1) tmp dest } towers1.hs:8:8: Couldn't match expected type `[Char]' with actual type `[Char] -> [Char]' In the return type of a call of `solve' Probable cause: `solve' is applied to too few arguments In a stmt of a 'do' block: solve (n - 1) tmp dest In the expression: do { solve (n - 1) src tmp; solve 1 src dest tmp; solve (n - 1) tmp dest } towers1.hs:11:5: Couldn't match expected type `[Char]' with actual type `IO ()' In the return type of a call of `putStrLn' In the first argument of `(++)', namely `putStrLn "move a disk from "' In the expression: putStrLn "move a disk from " ++ src ++ " to " ++ dest

Nevermind... it really is too few arguments. On 3/28/2014 6:00 PM, John M. Dlugosz wrote:
Can someone explain what's wrong here? What is the code below _really_ saying, vs what I meant? I don't understand the error messages yet.
== input == module Main ( main ) where
solve n src dest tmp = do solve (n-1) src tmp -- line 6 solve 1 src dest tmp solve (n-1) tmp dest -- line 8
solve 1 src dest _ = putStrLn "move a disk from " ++ src ++ " to " ++ dest -- line 11
main = do putStrLn "Towers of Hanoi problem" solve 5 "A" "B" "C"
== output == Prelude> :reload [1 of 1] Compiling Main ( towers1.hs, interpreted ) Failed, modules loaded: none. Prelude> towers1.hs:6:8: Couldn't match expected type `[a0]' with actual type `[Char] -> [Char]' In the return type of a call of `solve' Probable cause: `solve' is applied to too few arguments In a stmt of a 'do' block: solve (n - 1) src tmp In the expression: do { solve (n - 1) src tmp; solve 1 src dest tmp; solve (n - 1) tmp dest }
towers1.hs:8:8: Couldn't match expected type `[Char]' with actual type `[Char] -> [Char]' In the return type of a call of `solve' Probable cause: `solve' is applied to too few arguments In a stmt of a 'do' block: solve (n - 1) tmp dest In the expression: do { solve (n - 1) src tmp; solve 1 src dest tmp; solve (n - 1) tmp dest }
towers1.hs:11:5: Couldn't match expected type `[Char]' with actual type `IO ()' In the return type of a call of `putStrLn' In the first argument of `(++)', namely `putStrLn "move a disk from "' In the expression: putStrLn "move a disk from " ++ src ++ " to " ++ dest

OK, I'm really stuck now. This gives "out of memory" and doesn't print anything other than the first line of output. == source code == module Main ( main ) where solve n src dest tmp = do solve (n-1) src tmp dest solve 1 src dest tmp solve (n-1) tmp dest src solve 1 src dest _ = putStrLn ("move a disk from " ++ src ++ " to " ++ dest) main = do putStrLn "Towers of Hanoi problem" solve 5 "A" "B" "C" == end == Each recursive call is either 1 or (n-1) so it should count down 5,4,3,2,1 and stop the recursion. What am I missing?

On Fri, Mar 28, 2014 at 7:10 PM, John M. Dlugosz
Each recursive call is either 1 or (n-1) so it should count down 5,4,3,2,1 and stop the recursion.
What am I missing? It doesn't magically stop at 0; Integer (inferred type) is signed. Moreover, even if it were not signed, it would wrap around (or possibly throw an exception on some CPUs, but not on Intel). You need to include a check for 0 to stop the recursion. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On 3/28/2014 6:14 PM, Brandon Allbery wrote:
On Fri, Mar 28, 2014 at 7:10 PM, John M. Dlugosz
mailto:ngnr63q02@sneakemail.com> wrote: Each recursive call is either 1 or (n-1) so it should count down 5,4,3,2,1 and stop the recursion.
What am I missing?
It doesn't magically stop at 0; Integer (inferred type) is signed. Moreover, even if it were not signed, it would wrap around (or possibly throw an exception on some CPUs, but not on Intel). You need to include a check for 0 to stop the recursion.
I don't get it. When n == 1 it should match the second form, and that is not recursive. Ah, they are matched in order! (Yes, it works if I reverse the clauses) Hmm, so it figures out the type from all of them? I worried about putting specialized ones first because there is far less information.

On Fri, Mar 28, 2014 at 7:49 PM, John M. Dlugosz
On 3/28/2014 6:14 PM, Brandon Allbery wrote:
On Fri, Mar 28, 2014 at 7:10 PM, John M. Dlugosz < ngnr63q02@sneakemail.com mailto:ngnr63q02@sneakemail.com> wrote:
Each recursive call is either 1 or (n-1) so it should count down 5,4,3,2,1 and stop the recursion.
What am I missing?
It doesn't magically stop at 0; Integer (inferred type) is signed. Moreover, even if it were not signed, it would wrap around (or possibly throw an exception on some CPUs, but not on Intel). You need to include a check for 0 to stop the recursion.
I don't get it. When n == 1 it should match the second form, and that is not recursive.
Ah, they are matched in order! (Yes, it works if I reverse the clauses)
Hmm, so it figures out the type from all of them? I worried about putting
specialized ones first because there is far less information.
It uses all of them to get the type, yes. And the more specific pattern must come first; the first one always matches in this case because `n` doesn't give it any way not to match. If you had warnings enabled, the compiler should have warned you that the second form wouldn't be matched (although you may also need optimization turned on). The compiler doesn't see the different implementations as independent, and in fact doesn't see multiple implementations of the function at all at type resolution time; it's translated to a single function applying `case` to the parameters to determine which clause of the body to evaluate. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On 3/28/2014 6:56 PM, Brandon Allbery wrote:
It uses all of them to get the type, yes. And the more specific pattern must come first; the first one always matches in this case because `n` doesn't give it any way not to match. If you had warnings enabled, the compiler should have warned you that the second form wouldn't be matched (although you may also need optimization turned on).
I was wondering about that. I'll look for warning flags. I was loading into GHCi rather than running the compiler from the command line.
The compiler doesn't see the different implementations as independent, and in fact doesn't see multiple implementations of the function at all at type resolution time; it's translated to a single function applying `case` to the parameters to determine which clause of the body to evaluate.
Can they be spread out among different source files or be discontiguous within one file?

On Sat, Mar 29, 2014 at 12:13 AM, John M. Dlugosz
On 3/28/2014 6:56 PM, Brandon Allbery wrote:
The compiler doesn't see the different implementations as independent, and in fact doesn't
see multiple implementations of the function at all at type resolution
time; it's translated to a single function applying `case` to the parameters to determine which clause of the body to evaluate.
Can they be spread out among different source files or be discontiguous within one file?
Neither one; they must be together in the same file with nothing intervening, since they get rewritten into a single function. They also must all have the same number of parameters, even if one of them could take advantage of eta reduction (see http://www.haskell.org/haskellwiki/Eta_conversion), since the combination into a single function uses a common set of parameters. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On 3/28/2014 11:22 PM, Brandon Allbery wrote:
Can they be spread out among different source files or be discontiguous within one file?
Neither one; they must be together in the same file with nothing intervening, since they get rewritten into a single function. They also must all have the same number of parameters, even if one of them could take advantage of eta reduction
Many thanks.
participants (2)
-
Brandon Allbery
-
John M. Dlugosz