What can be improved on my first haskell program? - haskell

Here is my first Haskell program. What parts would you write in a better way?
-- Multiplication table
-- Returns n*n multiplication table in base b
import Text.Printf
import Data.List
import Data.Char
-- Returns n*n multiplication table in base b
mulTable :: Int -> Int -> String
mulTable n b = foldl (++) (verticalHeader n b w) (map (line n b w) [0..n])
where
lo = 2* (logBase (fromIntegral b) (fromIntegral n))
w = 1+fromInteger (floor lo)
verticalHeader :: Int -> Int -> Int -> String
verticalHeader n b w = (foldl (++) tableHeader columnHeaders)
++ "\n"
++ minusSignLine
++ "\n"
where
tableHeader = replicate (w+2) ' '
columnHeaders = map (horizontalHeader b w) [0..n]
minusSignLine = concat ( replicate ((w+1)* (n+2)) "-" )
horizontalHeader :: Int -> Int -> Int -> String
horizontalHeader b w i = format i b w
line :: Int -> Int -> Int -> Int -> String
line n b w y = (foldl (++) ((format y b w) ++ "|" )
(map (element b w y) [0..n])) ++ "\n"
element :: Int -> Int -> Int -> Int -> String
element b w y x = format (y * x) b w
toBase :: Int -> Int -> [Int]
toBase b v = toBase' [] v where
toBase' a 0 = a
toBase' a v = toBase' (r:a) q where (q,r) = v `divMod` b
toAlphaDigits :: [Int] -> String
toAlphaDigits = map convert where
convert n | n < 10 = chr (n + ord '0')
| otherwise = chr (n + ord 'a' - 10)
format :: Int -> Int -> Int -> String
format v b w = concat spaces ++ digits ++ " "
where
digits = if v == 0
then "0"
else toAlphaDigits ( toBase b v )
l = length digits
spaceCount = if (l > w) then 0 else (w-l)
spaces = replicate spaceCount " "

Here are some suggestions:
To make the tabularity of the computation more obvious, I would pass the list [0..n] to the line function rather than passing n.
I would further split out the computation of the horizontal and vertical axes so that they are passed as arguments to mulTable rather than computed there.
Haskell is higher-order, and almost none of the computation has to do with multiplication. So I would change the name of mulTable to binopTable and pass the actual multiplication in as a parameter.
Finally, the formatting of individual numbers is repetitious. Why not pass \x -> format x b w as a parameter, eliminating the need for b and w?
The net effect of the changes I am suggesting is that you build a general higher-order function for creating tables for binary operators. Its type becomes something like
binopTable :: (i -> String) -> (i -> i -> i) -> [i] -> [i] -> String
and you wind up with a much more reusable function—for example, Boolean truth tables should be a piece of cake.
Higher-order and reusable is the Haskell Way.

You don't use anything from import Text.Printf.
Stylistically, you use more parentheses than necessary. Haskellers tend to find code more readable when it's cleaned of extraneous stuff like that. Instead of something like h x = f (g x), write h = f . g.
Nothing here really requires Int; (Integral a) => a ought to do.
foldl (++) x xs == concat $ x : xs: I trust the built-in concat to work better than your implementation.
Also, you should prefer foldr when the function is lazy in its second argument, as (++) is – because Haskell is lazy, this reduces stack space (and also works on infinite lists).
Also, unwords and unlines are shortcuts for intercalate " " and concat . map (++ "\n") respectively, i.e. "join with spaces" and "join with newlines (plus trailing newline)"; you can replace a couple things by those.
Unless you use big numbers, w = length $ takeWhile (<= n) $ iterate (* b) 1 is probably faster. Or, in the case of a lazy programmer, let w = length $ toBase b n.
concat ( (replicate ((w+1)* (n+2)) "-" ) == replicate ((w+1) * (n+2)) '-' – not sure how you missed this one, you got it right just a couple lines up.
You do the same thing with concat spaces, too. However, wouldn't it be easier to actually use the Text.Printf import and write printf "%*s " w digits?

Norman Ramsey gave excellent high-level (design) suggestions; Below are some low-level ones:
First, consult with HLint. HLint is a friendly program that gives you rudimentary advice on how to improve your Haskell code!
In your case HLint gives 7 suggestions. (mostly about redundant brackets)
Modify your code according to HLint's suggestions until it likes what you feed it.
More HLint-like stuff:
concat (replicate i "-"). Why not replicate i '-'?
Consult with Hoogle whenever there is reason to believe that a function you need is already available in Haskell's libraries. Haskell comes with tons of useful functions so Hoogle should come in handy quite often.
Need to concatenate strings? Search for [String] -> String, and voila you found concat. Now go replace all those folds.
The previous search also suggested unlines. Actually, this even better suits your needs. It's magic!
Optional: pause and thank in your heart to Neil M for making Hoogle and HLint, and thank others for making other good stuff like Haskell, bridges, tennis balls, and sanitation.
Now, for every function that takes several arguments of the same type, make it clear which means what, by giving them descriptive names. This is better than comments, but you can still use both.
So
-- Returns n*n multiplication table in base b
mulTable :: Int -> Int -> String
mulTable n b =
becomes
mulTable :: Int -> Int -> String
mulTable size base =
To soften the extra characters blow of the previous suggestion: When a function is only used once, and is not very useful by itself, put it inside its caller's scope in its where clause, where it could use the callers' variables, saving you the need to pass everything to it.
So
line :: Int -> Int -> Int -> Int -> String
line n b w y =
concat
$ format y b w
: "|"
: map (element b w y) [0 .. n]
element :: Int -> Int -> Int -> Int -> String
element b w y x = format (y * x) b w
becomes
line :: Int -> Int -> Int -> Int -> String
line n b w y =
concat
$ format y b w
: "|"
: map element [0 .. n]
where
element x = format (y * x) b w
You can even move line into mulTable's where clause; imho, you should.
If you find a where clause nested inside another where clause troubling, then I suggest to change your indentation habits. My recommendation is to use consistent indentation of always 2 or always 4 spaces. Then you can easily see, everywhere, where the where in the other where is at. ok
Below's what it looks like (with a few other changes in style):
import Data.List
import Data.Char
mulTable :: Int -> Int -> String
mulTable size base =
unlines $
[ vertHeaders
, minusSignsLine
] ++ map line [0 .. size]
where
vertHeaders =
concat
$ replicate (cellWidth + 2) ' '
: map horizontalHeader [0 .. size]
horizontalHeader i = format i base cellWidth
minusSignsLine = replicate ((cellWidth + 1) * (size + 2)) '-'
cellWidth = length $ toBase base (size * size)
line y =
concat
$ format y base cellWidth
: "|"
: map element [0 .. size]
where
element x = format (y * x) base cellWidth
toBase :: Integral i => i -> i -> [i]
toBase base
= reverse
. map (`mod` base)
. takeWhile (> 0)
. iterate (`div` base)
toAlphaDigit :: Int -> Char
toAlphaDigit n
| n < 10 = chr (n + ord '0')
| otherwise = chr (n + ord 'a' - 10)
format :: Int -> Int -> Int -> String
format v b w =
spaces ++ digits ++ " "
where
digits
| v == 0 = "0"
| otherwise = map toAlphaDigit (toBase b v)
spaces = replicate (w - length digits) ' '

0) add a main function :-) at least rudimentary
import System.Environment (getArgs)
import Control.Monad (liftM)
main :: IO ()
main = do
args <- liftM (map read) $ getArgs
case args of
(n:b:_) -> putStrLn $ mulTable n b
_ -> putStrLn "usage: nntable n base"
1) run ghc or runhaskell with -Wall; run through hlint.
While hlint doesn't suggest anything special here (only some redundant brackets), ghc will tell you that you don't actually need Text.Printf here...
2) try running it with base = 1 or base = 0 or base = -1

If you want multiline comments use:
{- A multiline
comment -}
Also, never use foldl, use foldl' instead, in cases where you are dealing with large lists which must be folded. It is more memory efficient.

A brief comments saying what each function does, its arguments and return value, is always good. I had to read the code pretty carefully to fully make sense of it.
Some would say if you do that, explicit type signatures may not be required. That's an aesthetic question, I don't have a strong opinion on it.
One minor caveat: if you do remove the type signatures, you'll automatically get the polymorphic Integral support ephemient mentioned, but you will still need one around toAlphaDigits because of the infamous "monomorphism restriction."

Related

Correct way to format Haskell functions considering scope?

I'm new to Haskell. I've put together a basic Caesar Cipher, it works, but it's very messy and difficult to read.
caesarCipher :: Int -> String -> String
caesarCipher n xs = [shift n x | x <- xs]
shift n c = num2let ((let2num c + n) `mod` 26)
alphabet = ['a'..'z']
let2num c = head[ b | (a,b) <- zip alphabet [0..length alphabet], a==c]
num2let = (!!) alphabet
What is the "correct" way in Haskell to format functions that consist of multiple variables and expressions, and should I be considering the scope of the variables? And other than efficiency based suggestions have I made any other "major" mistakes?
This is my attempt:
caesarCipher n xs = let
shift n c = num2let ((let2num c + n) `mod` 26) where
alphabet = ['a'..'z']
let2num c = head[ b | (a,b) <- zip alphabet [0..length alphabet], a==c]
num2let = (!!) alphabet
in [shift n x | x <- xs]
I would first of all rewrite some functions. For example. zip alphabet [0 .. length alphabet] can be replaced with zip alphabet [0..], since the zip will stop from the moment one of the lists is exhausted. Making use of (!!) and head is often not good practice, since these functions are non-total: if the index is too large, or the list is empty, (!!) and head will error respectively.
We can define helper functions, for example for num2let:
import Data.Char(chr, ord)
num2let :: Int -> Char
num2let n = chr (n + ord 'a')
here num2let will map 0 to 'a', 1 to 'b', etc.
let2num can be done in a similar manner:
import Data.Char(ord)
let2num :: Char -> Int
let2num c = ord c - ord 'a'
So now we can define caesarCipher as:
caesarCipher :: Int -> String -> String
caesarCipher n = map (num2let . (`mod 26`) . (n+) . let2num)
So that would look in full as:
import Data.Char(chr, ord)
num2let :: Int -> Char
num2let n = chr (n + ord 'a')
let2num :: Char -> Int
let2num c = ord c - ord 'a'
caesarCipher :: Int -> String -> String
caesarCipher n = map (num2let . (`mod` 26) . (n+) . let2num)
The nice thing is that you can here reuse the let2num and num2let for other functions.
Normally top-level functions are separated with a blank line, and are given a signature. This is not necessary, but makes it usually more convenient to read.

How can you use the result of a function as a variable in another function in Haskell?

I'm trying to learn how to use Haskell and now I have to make a program that takes a integer n and a string k and every letter of that string will be moved n places to the right in the alphabet. At this moment I've got the next code:
import Data.Char
main = do
x <- read getLine :: Int
y <- getLine
caesar x y
result :: String
rotate :: Int -> Char -> [Char]
rotate a b = [chr ((a + ord b) `mod` ord 'z' + ord 'a')]
caesar :: Int -> String -> ()
caesar moving text= do
rotatespecific moving text 0
putStrLn result
rotatespecific :: Int -> String -> Int -> ()
rotatespecific moving text place = do
if place < length text
then
result ++ rotate (moving (text !! place))
rotatespecific (moving text (place + 1))
else
if place == length text
then
result ++ rotate (moving (text !! place))
But I can't compile it because it still gives me the same error message:
parse error (possibly incorrect indentation or mismatched brackets)
|
28 | result ++ rotate (moving (text !! place))
| ^
But I can't see what's wrong with my syntax. I first thought it had something to do with using a Char as parameter for my function but I was wrong because text !! place should give a char and not a [char]. So what's wrong with what I'm doing?
After some edit I got this, but it still doesn't work:
import Data.Char
main = do
xr <- getLine
let x = read xr :: Int
y <- getLine
putStrLn (rotatespecific (x y 0))
rotate :: Int -> Char -> [Char]
rotate a b = [chr ((a + ord b) `mod` ord 'z' + ord 'a')]
rotatespecific :: Int -> String -> Int -> String
rotatespecific moving text place = do
if place < length text
then do
help <- text !! place
h <- rotate (moving help)
a <- rotatespecific (moving text (place + 1))
b <- h ++ a
return b
else
if place == length text
then do
return rotate (moving (text !! place))
else
return ()
The immediate problem is that every if must have an else. You got a parse error at the end because the parser is expecting more, namely an else for that if place == length text.
When you fix this you will have more problems, because you are treating Haskell like an imperative language, and that's not how she likes to be treated. It seems like you think
result ++ newstuff
will mutate result, adding newstuff to the end of it. But Haskell doesn't mutate. Instead, this expression result ++ newstuff is the list that results when you concatenate result and newstuff, but result itself remains unchanged.
ghci> let result = [1,2,3]
ghci> result ++ [4,5,6]
[1,2,3,4,5,6]
ghci> result
[1,2,3]
rotatespecific must return the rotated string, rather than trying to mutate it into existence. The only way functions may communicate is by returning results computed from their arguments -– they may not manipulate any "global" state like result. A function that returns () is guaranteed to be useless.
rotatespecific :: Int -> String -> Int -> String
Delete the result "global variable" (which does not mean what you think it means) and focus on defining rotatespecific in a way that it returns the rotated string.
I would also recommend commenting out main and caesar for now until you have rotatespecific compiling and working when you test it in ghci.
I feel like this is an appropriate time to just show an example, because there are a lot of little problems. I'm not going to fix logic bugs, but I've fixed your syntax. Hopefully this gets you unstuck.
rotatespecific :: Int -> String -> Int -> String
rotatespecific moving text place =
if place < length text then
-- use let .. in instead of do/bind (<-) in pure functions.
let help = text !! place
-- multiple arguments are given after the function, no parentheses
h = rotate moving help
-- use parentheses around an argument if it is a complex expression
-- (anything more than a variable name)
a = rotatespecific moving text (place+1)
b = h ++ a
in b
else
if place == length text then
rotate moving (text !! place)
else
undefined -- you must decide what String to return in this case.
After you have this function working as intended, and only then, open this sealed envelope. ♥️
rotatespecific :: Int -> String -> String
rotatespecific moving text = concatMap (rotate moving) text

How to convert a Rational into a "pretty" String?

I want to display some Rational values in their decimal expansion. That is, instead of displaying 3 % 4, I would rather display 0.75. I'd like this function to be of type Int -> Rational -> String. The first Int is to specify the maximum number of decimal places, since Rational expansions may be non-terminating.
Hoogle and the haddocks for Data.Ratio didn't help me. Where can I find this function?
You can make it. Not elegant, but does the job:
import Numeric
import Data.Ratio
display :: Int -> Rational -> String
display n x = (showFFloat (Just n) $ fromRat x) ""
Here is an arbitrary precision solution that doesn't use floats:
import Data.Ratio
display :: Int -> Rational -> String
display len rat = (if num < 0 then "-" else "") ++ (shows d ("." ++ take len (go next)))
where
(d, next) = abs num `quotRem` den
num = numerator rat
den = denominator rat
go 0 = ""
go x = let (d, next) = (10 * x) `quotRem` den
in shows d (go next)
Arbitrary precision version that re-uses library code:
import Data.Number.CReal
display :: Int -> Rational -> String
display digits num = showCReal digits (fromRational num)
I know I've seen a function before that converts rationals into digits in a way that's easier to inspect (i.e. that makes it quite clear where the digits start repeating), but I can't seem to find it now. In any case, it's not hard to write, if that turns out to be a need; you just code up the usual long-division algorithm and watch for divisions you've already done.
Here's one that I wrote a few weeks ago. You can specify the number of decimals you want (correctly rounded), or just pass Nothing in which case it will print the full precision, including marking the repeated decimals.
module ShowRational where
import Data.List(findIndex, splitAt)
-- | Convert a 'Rational' to a 'String' using the given number of decimals.
-- If the number of decimals is not given the full precision is showed using (DDD) for repeating digits.
-- E.g., 13.7/3 is shown as \"4.5(6)\".
showRational :: Maybe Int -> Rational -> String
showRational (Just n) r =
let d = round (abs r * 10^n)
s = show (d :: Integer)
s' = replicate (n - length s + 1) '0' ++ s
(h, f) = splitAt (length s' - n) s'
in (if r < 0 then "-" else "") ++ h ++ "." ++ f
-- The length of the repeating digits is related to the totient function of the denominator.
-- This means that the complexity of computing them is at least as bad as factoring, i.e., it quickly becomes infeasible.
showRational Nothing r =
let (i, f) = properFraction (abs r) :: (Integer, Rational)
si = if r < 0 then "-" ++ show i else show i
decimals f = loop f [] ""
loop x fs ds =
if x == 0 then
ds
else
case findIndex (x ==) fs of
Just i -> let (l, r) = splitAt i ds in l ++ "(" ++ r ++ ")"
Nothing -> let (c, f) = properFraction (10 * x) :: (Integer, Rational) in loop f (fs ++ [x]) (ds ++ show c)
in if f == 0 then si else si ++ "." ++ decimals f
import Data.List as L
import Data.Ratio
display :: (Integral i, Show i) => Int -> Ratio i -> String
display len rat = (if num < 0 then "-" else "") ++ show ip ++ "." ++ L.take len (go (abs num - ip * den))
where
num = numerator rat
den = denominator rat
ip = abs num `quot` den
go 0 = ""
go x = shows d (go next)
where
(d, next) = (10 * x) `quotRem` den

How do I add the contents of a string?

Im am making a function which compares two strings to see if one is a rearrangement of the other. for example "hhe" and "heh" would produce true but "hhe" and "hee" would be false. I thought I could do this by summing the elements of the string and seeing if they are the same. I am knew to haskell, so I dont know if I can sum chars like in C. Code so far:
comp :: String -> String-> Bool
comp x y = (sum x) == (sum y)
This produces an error when compiling.
You can first sort, then compare the strings
import Data.List
import Data.Function
comp = (==) `on` sort
which can then be used like this
"abcd" `comp` "dcba" --yields True
It doesn't make sense to "sum" two strings. Use permutations instead:
comp :: String -> String -> Bool
comp x = (`elem` permutations x)
Live demo
Though there are problems with your implementation, as suggested by others, the direct answer to your question is that you can first convert characters to Int (a type that supports arithmetic) with fromEnum.
> sum . map fromEnum $ "heh"
309
Taking your example code at face value, the problem with it is that Char doesn't implement Num, so sum :: Num a => [a] -> a is incompatible.
We can fix that, however, by using fromEnum to convert the Chars to Ints:
isPermutationOf :: String -> String-> Bool
isPermutationOf x y = hash x == hash y
where hash = sum . map fromEnum
And this will work on your example case:
λ isPermutationOf "hhe" "heh"
True
The downside is that it also has some false positives:
λ isPermutationOf "AAA" "ab"
True
We can try to reduce those somewhat by making sure that the lengths, maxes, and mins of the inputs are the same:
isPermutationOf :: String -> String-> Bool
isPermutationOf x y = hash x == hash y && maximum x == maximum y && minimum x == minimum y
where hash = sum . map fromEnum
But though that catches some cases
λ isPermutationOf "AAA" "ab"
False
It doesn't catch them all
λ isPermutationOf "abyz" "acxz"
True
To do that, we really need to make sure we've got the same number of each Char in both inputs. We could solve this by using a Data.Map.Map to store the counts of each Char or by using Data.List.sort to sort each of the inputs, but if we only want to use the Prelude, we'll need to roll our own solution.
There's any number of examples on how to write quicksort in haskell out there, so I'm not going to tell you how to do that. So here's a dumb isPermutationOf that uses math instead.
isPermutationOf xs ys = all (\k -> powsum k as == powsum k bs) [0..n]
where as = map fromEnum xs
bs = map fromEnum ys
n = length xs
powsum k zs = sum (map (^k) zs)
Basically, we can view an n-length string as a set of n unknowns. isPermutationOf checks the n+1 equations:
eq0: x00 + x10 + ... + xn-10 = y00 + y10 + ... + ym-10
eq1: x01 + x11 + ... + xn-11 = y01 + y11 + ... + ym-11
eq2: x02 + x12 + ... + xn-12 = y02 + y12 + ... + ym-12
...
eqn: x0n + x1n + ... + xn-1n = y0n + y1n + ... + ym-1n
eq0 is essentially a length check. Given xs, the other n equations work out to n equations for n unknowns, which will give us a solution for ys unique up to permutation.
But really, you should use a (bucket) sort instead, because the above algorithm is O(n^2), which is slow for this kind of check.
if you do not want to use standard library(learning purpose) function, you can quickSort both string and check for equality of string (bonus: quickSort)
isEqual :: String -> String -> Bool
isEqual a b = sortString a == sortString b
where
sortString :: String -> String
sortString [] = []
sortString (x:xs) = sortString (filter (<x) xs) ++ [x] ++ sortString (filter (>=x) xs)

How do I recursively use newStdGen in Haskell? (to get different random results on each iteration)

I use System.Random and System.Random.Shuffle to shuffle the order of characters in a string, I shuffle it using:
shuffle' string (length string) g
g being a getStdGen.
Now the problem is that the shuffle can result in an order that's identical to the original order, resulting in a string that isn't really shuffled, so when this happens I want to just shuffle it recursively until it hits a a shuffled string that's not the original string (which should usually happen on the first or second try), but this means I need to create a new random number generator on each recursion so it wont just shuffle it exactly the same way every time.
But how do I do that? Defining a
newg = newStdGen
in "where", and using it results in:
Jumble.hs:20:14:
Could not deduce (RandomGen (IO StdGen))
arising from a use of shuffle'
from the context (Eq a)
bound by the inferred type of
shuffleString :: Eq a => IO StdGen -> [a] -> [a]
at Jumble.hs:(15,1)-(22,18)
Possible fix:
add an instance declaration for (RandomGen (IO StdGen))
In the expression: shuffle' string (length string) g
In an equation for `shuffled':
shuffled = shuffle' string (length string) g
In an equation for `shuffleString':
shuffleString g string
= if shuffled == original then
shuffleString newg shuffled
else
shuffled
where
shuffled = shuffle' string (length string) g
original = string
newg = newStdGen
Jumble.hs:38:30:
Couldn't match expected type `IO StdGen' with actual type `StdGen'
In the first argument of `jumble', namely `g'
In the first argument of `map', namely `(jumble g)'
In the expression: (map (jumble g) word_list)
I'm very new to Haskell and functional programming in general and have only learned the basics, one thing that might be relevant which I don't know yet is the difference between "x = value", "x <- value", and "let x = value".
Complete code:
import System.Random
import System.Random.Shuffle
middle :: [Char] -> [Char]
middle word
| length word >= 4 = (init (tail word))
| otherwise = word
shuffleString g string =
if shuffled == original
then shuffleString g shuffled
else shuffled
where
shuffled = shuffle' string (length string) g
original = string
jumble g word
| length word >= 4 = h ++ m ++ l
| otherwise = word
where
h = [(head word)]
m = (shuffleString g (middle word))
l = [(last word)]
main = do
g <- getStdGen
putStrLn "Hello, what would you like to jumble?"
text <- getLine
-- let text = "Example text"
let word_list = words text
let jumbled = (map (jumble g) word_list)
let output = unwords jumbled
putStrLn output
This is pretty simple, you know that g has type StdGen, which is an instance of the RandomGen typeclass. The RandomGen typeclass has the functions next :: g -> (Int, g), genRange :: g -> (Int, Int), and split :: g -> (g, g). Two of these functions return a new random generator, namely next and split. For your purposes, you can use either quite easily to get a new generator, but I would just recommend using next for simplicity. You could rewrite your shuffleString function to something like
shuffleString :: RandomGen g => g -> String -> String
shuffleString g string =
if shuffled == original
then shuffleString (snd $ next g) shuffled
else shuffled
where
shuffled = shuffle' string (length string) g
original = string
End of answer to this question
One thing that might be relevant which I don't know yet is the difference between "x = value", "x <- value", and "let x = value".
These three different forms of assignment are used in different contexts. At the top level of your code, you can define functions and values using the simple x = value syntax. These statements are not being "executed" inside any context other than the current module, and most people would find it pedantic to have to write
module Main where
let main :: IO ()
main = do
putStrLn "Hello, World"
putStrLn "Exiting now"
since there isn't any ambiguity at this level. It also helps to delimit this context since it is only at the top level that you can declare data types, type aliases, and type classes, these can not be declared inside functions.
The second form, let x = value, actually comes in two variants, the let x = value in <expr> inside pure functions, and simply let x = value inside monadic functions (do notation). For example:
myFunc :: Int -> Int
myFunc x =
let y = x + 2
z = y * y
in z * z
Lets you store intermediate results, so you get a faster execution than
myFuncBad :: Int -> Int
myFuncBad x = (x + 2) * (x + 2) * (x + 2) * (x + 2)
But the former is also equivalent to
myFunc :: Int -> Int
myFunc x = z * z
where
y = x + 2
z = y * y
There are subtle difference between let ... in ... and where ..., but you don't need to worry about it at this point, other than the following is only possible using let ... in ..., not where ...:
myFunc x = (\y -> let z = y * y in z * z) (x + 2)
The let ... syntax (without the in ...) is used only in monadic do notation to perform much the same purpose, but usually using values bound inside it:
something :: IO Int
something = do
putStr "Enter an int: "
x <- getLine
let y = myFunc (read x)
return (y * y)
This simply allows y to be available to all proceeding statements in the function, and the in ... part is not needed because it's not ambiguous at this point.
The final form of x <- value is used especially in monadic do notation, and is specifically for extracting a value out of its monadic context. That may sound complicated, so here's a simple example. Take the function getLine. It has the type IO String, meaning it performs an IO action that returns a String. The types IO String and String are not the same, you can't call length getLine, because length doesn't work for IO String, but it does for String. However, we frequently want that String value inside the IO context, without having to worry about it being wrapped in the IO monad. This is what the <- is for. In this function
main = do
line <- getLine
print (length line)
getLine still has the type IO String, but line now has the type String, and can be fed into functions that expect a String. Whenever you see x <- something, the something is a monadic context, and x is the value being extracted from that context.
So why does Haskell have so many different ways of defining values? It all comes down to its type system, which tries really hard to ensure that you can't accidentally launch the missiles, or corrupt a file system, or do something you didn't really intend to do. It also helps to visually separate what is an action, and what is a computation in source code, so that at a glance you can tell if an action is being performed or not. It does take a while to get used to, and there are probably valid arguments that it could be simplified, but changing anything would also break backwards compatibility.
And that concludes today's episode of Way Too Much Information(tm)
(Note: To other readers, if I've said something incorrect or potentially misleading, please feel free to edit or leave a comment pointing out the mistake. I don't pretend to be perfect in my descriptions of Haskell syntax.)

Resources