Missing colon: the function showRun
should yield a string of the form "be: 2\n"
.
Thanks to Nobuo Yamashita for spotting this.
In the definition of convert3
the guard in the second clause should be t==0
, not n==0
.
Thanks to Kevin Boulain for spotting this.
The argument type of showEntry
should be (Label,[Word])
, not [(Label,[Word])]
.
Thanks to Daniel Alonso and Zachariah Levine for spotting this.
The URL for the paper History of Haskell has changed; perhaps the DOI 10.1145/1238844.1238856 is a more robust reference.
Thanks to David Johnson-Davies for spotting this.
"Operator names consist only of symbols."
Thanks to Nobuo Yamashita for spotting this.
For consistency with p9, "back quotes" should be "back-quotes".
Thanks to Gilbert Bonthonnou for spotting this.
Missing close quote: the string should be
"Hello" ++ "\n" ++ ...
Thanks to Nobuo Yamashita and Gebrezgi Bocretsion for spotting this.
The three occurrences of sqrt d
should be sqrt disc
.
Thanks to Zachariah Levine for spotting this.
The function toUpper
is not exported from the prelude, so the question should be about "the name of the standard function".
Thanks to Nobuo Yamashita for spotting this.
The type of (-)
is Num a => a -> a -> a
.
Thanks to Nobuo Yamashita for spotting this.
In fact, unwords
is neither a left nor a right inverse of words
, as the documentation demonstrates.
Thanks to Adrian Baran for spotting this.
The last part of Exercise E says "Finally, count the number of functions with type Maybe a -> Maybe a
". The answer incorrectly states that there are six. In fact there may be more or fewer.
First off, the question is not posed sufficiently precisely. There are two kinds of ambiguity. Firstly, the function (\x -> undefined)
has type a -> b
, so certainly also has type Maybe a -> Maybe a
. Should this also be included in the count, or do we only want the functions f
for which the Haskell typechecker responds
>gchi :type f f : Maybe a -> Maybe a
Secondly, do we mean arbitrary mathematical function, or functions that can be defined in Haskell? In the latter case the situation is complicated by the fact that Haskell defines a primitive function seq
(first mentioned on page 150) that can add a few more functions to the list.
Allowing functions that (i) have a possibly more general type than Maybe a -> Maybe a
; (ii) are Haskell definable without using seq
, then the current count is 15 functions.
Applied to Nothing
the function can return three values: Nothing
, undefined
, or Just undefined
. Applied to Just x
the function can return four values: Nothing
, undefined
, Just x
, or Just undefined
. That gives 12 functions. All these functions are strict. But there are also three more non-strict functions, two of which are const Nothing
and const (Just undefined)
. The third one is trickier to spot and was found by Nick Smallbone who wrote a program to enumerate the functions:
f x = Just (case x of Nothing -> undefined; Just v -> v)
Restricting the question to functions for which Haskell infers the specific type Maybe a -> Maybe a
, there are just four functions:
f1 x = case x of Nothing -> Nothing; Just v -> Just v f2 x = case x of Just v -> Just v f3 x = case x of Nothing -> Just undefined; Just v -> Just v f4 x = Just (case x of Nothing -> undefined; Just v -> v)
In each of these functions the value Just x
is returned if the argument is Just x
, which is necessary and sufficient to ensure a target type of Maybe a
.
Thanks to Matthew Brecknall, Lennart Augustsson, Patrick Smears, John Hughes, Nick Smallbone, Ganesh Sittampalan, Jeremy Gibbons and others for helping with the exercise.
The definition should be
exp x n | n == 0 = 1 | n == 1 = x | even n = exp (x*x) m | odd n = x*exp (x*x) m where m = n `div` 2
Thanks to Martin Vlk for spotting this.
The number of multiplications is wrong; the text should read "Dick's program takes at most 2* floor (log n ) multiplications, where floor returns...".
Thanks to Zachariah Levine for spotting this.
The Haskell 98 and Haskell 2010 reports both assert that Num
is a subclass of both Eq
and Show
, but GHC 7.4.1 removed these superclass constraints.
Thanks to Sencer Burak Somuncuoğlu for spotting this.
Line 4 should read for positive x
and y
we have 0 <= x `mod` y < y
Thanks to Chenguang Li for spotting this.
until f p x
should read until p f x
.
Thanks to Gilbert Bonthonnou for spotting this.
The type of (<=)
should read
(<=) :: Ord a => a -> a -> Bool
Thanks to Emmanual Viaud for spotting this.
The reference to "Exercise E" should be to "Exercise F".
Thanks to Semen Trygubenko for spotting this.
The explanations of (^^)
and (**)
should read: (^^)
raises any fractional number to any integral power (including negative integers); and (**)
takes two floating-point arguments.
Thanks to Nobuo Yamashita for spotting this.
There's a redundant parenthesis before takeWhile
; compare with Clever Dick's actual solution on p52.
Thanks to Nobuo Yamashita and Carlos Suberviola Oroz for spotting this.
Replace 2 + -3
with 3 + -2
.
Thanks to A Van Emmenis for spotting this.
fromInteger
should be replaced (twice) by fromIntegral
.
Thanks to Zhe Zhang for spotting this.
A minimal complete Ord
instance requires a definition of either compare
or (<=)
.
Thanks to Gihan Marasingha for spotting this.
Replace text with "When m
and n
are integers with m<n
we can write", and change [m, n .. p]
to [m, m+(n-m), m+2(n-m), ... ,m+a(n-m)]
, where a
is the largest integer such that m+a(n-m) <= p
.
Thanks to Zhe Zhang for spotting this.
Ramanujan's first name is "Srinivasa".
Thanks to Francisco Lieberich for spotting this.
You can't make the type synonym Pair
an instance of the class Bifunctor
; it would have to be a data
declaration.
Thanks to Gihan Marasingha and Rui Peng for spotting this.
The last prompt in the GHCi session should be ghci>
.
Thanks to Nobuo Yamashita for spotting this.
Strictly speaking, the two expressions should have more ellipses: 1+(1+(1+...(1+0)...))
and loop ((...(((0+1)+1)+1)...)+1,[])
.
Thanks to Nobuo Yamashita for spotting this.
The type of digits
is better as [Digit]
than [Char]
.
Thanks to Francisco Lieberich for spotting this.
In the last step of the calculation, the definition of pruneBy
should read
pruneBy f = f. map pruneRow . f
Thanks to Eric Yi-Hsun Huang and Nobuo Yamashita for spotting this.
The argument to safe
should be cm
, not m
.
Thanks to Qiao Haiyan for spotting this.
Two occurrences of filter p
should be filter valid
.
Thanks to Carlos Suberviola Oroz, Juan Manuel Gimeno, Paul Horsfall, and Francisco Lieberich for spotting this.
The first equation in Exercise C should be
any p = not . all (not . p)
Thanks to Akiel Khan for spotting this.
The function transpose
is used here (in the answer to Exercise A), but only defined in Exercise B, as a synonym for cols
. If you read the former before the latter, it's a forward reference.
Thanks to Francisco Lieberich for spotting this.
Misplaced/missing parentheses in the lhs calculation of "Case m+1":
exp x ((m + 1) + n) = exp x ((m + n) + 1)
Thanks to Torsten Grust for spotting this.
Missing parenthesis; the line should be
foldr f e (x:(xs ++ ys))
Thanks to Gihan Marasingha for spotting this.
In the penultimate block on the page, the last line should be
f x:(xs ++ ys) = (f x:xs) ++ ys
Thanks to Semen Trygubenko for spotting this.
Missing parenthesis in the definition of fpart
:
fpart xs = read ('0':dropWhile (/= '.') xs) :: Float
Thanks to Francisco Lieberich for spotting this.
In the []
case, in the third step, only rule map.1
is used; and in the x:xs
case, in the third step, only rule map.2
is used. Thanks to John Tasto for spotting this.
In the x:xs
case, the last expression should be
e:scanl f (f e x) xs
Thanks to Semen Trygubenko for spotting this.
Remove the full stop at the end of the line:
scanl f e undefined = e : undefined
Thanks to Nobuo Yamashita for spotting this.
The x
and xs
should be in typewriter font.
Thanks to Nobuo Yamashita for spotting this.
Missing argument in the second case for mult
:
mult (Succ x) y = mult x y + y
Thanks to Torsten Grust for spotting this.
In Exercise I, the left-hand side should read scanr f e
, not scan r f e
.
Thanks to Zhe Zhang for spotting this.
Variables xs
and p
should be in typewriter font.
Thanks to Nobuo Yamashita for spotting this.
Variable f
should be in typewriter font.
Thanks to Nobuo Yamashita for spotting this.
In the Answer to Exercise F, the two occurrences of foldl g e
in the right column of Case []
should be replaced by foldr g e
.
Thanks to Zhe Zhang for spotting this.
The scan
should be scanr
.
Thanks to Nobuo Yamashita, Carlos Suberviola Oroz, and Francisco Lieberich for spotting this.
The foo 1000
should be foo2 1000
.
Thanks to Nobuo Yamashita for spotting this.
The function foldl'
is in the library Data.List
, not in the prelude.
Thanks to Nobuo Yamashita and Peter Salvi for spotting this.
sumlem
should be sumlen
.
Thanks to Jingjie Yang for spotting this.
Rename variable input
to x
for consistency with the two later examples.
Thanks to Nobuo Yamashita and Francisco Lieberich for spotting this.
Should read "the minimum of a list".
Replace O(1) by Θ(1).
Thanks to Zhe Zhang for spotting this.
The final expression should be Θ( mk + m 2n ).
Thanks to Carlos Suberviola Oroz for spotting this.
The function cp
was discussed at the end of the previous section, not the beginning of this one.
Thanks to Nobuo Yamashita for spotting this.
Two unbalanced parenthesis pairs: T (reverse
( n )) = T (revcat
( n ,0))
Thanks to Nobuo Yamashita, Semen Trygubenko, Qiao Haiyan, Carlos Suberviola Oroz, and Francisco Lieberich for spotting this.
The left-hand side s(1,t) should be s(1,k) .
Thanks to Carlos Suberviola Oroz and Francisco Lieberich for spotting this.
The last line of the calculation at the top of the page should read
x:labcat us (labcat vs xs)
Thanks to Peter Salvi and Nobuo Yamashita for spotting this.
The second argument is missing from the left-hand side in the second clause of the definition of labcat
:
labcat (Node x us:vs) xs = x:labcat us (labcat vs xs)
Thanks to Carlos Suberviola Oroz, Francisco Lieberich, and Matthew Towers for spotting this.
Redundant parenthesis: the right-hand side should read Θ(1) + T (labcat
)(1, k , n )
Thanks to Carlos Suberviola Oroz and Francisco Lieberich for spotting this.
The last line is missing argument xs
: sortp x xs (y:us) vs
Thanks to Peter Salvi, Carlos Suberviola Oroz, and Francisco Lieberich for spotting this.
The list to sort should be [3,4,1,2]
rather than [3,4,2,1]
, for consistency with the answer.
Thanks to Peter Salvi, Francisco Lieberich, and Matthew Towers for spotting this.
The k should be a superscript: the sum is Σ i=0 kΘ(2 k) .
Thanks to Qiao Haiyan for spotting this.
Missing a closing parenthesis on the first and fourth lines of the calculation.
Thanks to Nobuo Yamashita, Carlos Suberviola Oroz, Francisco Lieberich, and Matthew Towers for spotting this.
On the last line, variable z
should be x
. The question stipulates that part
should made be local to partition
, which the answer doesn't do.
Thanks to Nobuo Yamashita and Francisco Lieberich for spotting this.
The σ should be a Σ , and the argument to Θ should be j rather than n : the sum is Σ j=0 nΘ(j) .
Thanks to Qiao Haiyan, Carlos Suberviola Oroz, Francisco Lieberich, and Matthew Towers for spotting this.
The third clause of the key property should yield ys!!(k-(n+1))
, and similarly in the definition of select
.
Thanks to Carlos Suberviola Oroz and Francisco Lieberich for spotting this.
Redundant close parenthesis on the left-hand side.
Thanks to Carlos Suberviola Oroz and Matthew Towers for spotting this.
Replace the definition of nestl
by
nestl i = concat . map (indent i)
Thanks to Dimitris Orfanos for spotting this.
The definitions can be in a file called Pretty.lhs
or Pretty.hs
, depending on whether or not the code is literate.
Thanks to Nobuo Yamashita for spotting this.
Haskell export syntax: ... to export all the constructors we can write Doc(..)
in the export list ...
Thanks to Torsten Grust for spotting this.
Redundant ::
in the type declaration.
Thanks to Nobuo Yamashita for spotting this.
Replace iterate3 (2*1)
by iterate3 (2*) 1
(three times).
Thanks to Zhe Zhang for spotting this.
Should read:
foldr1 f (x:xs) = f x (foldlr1 f xs)
Thanks to Matthew Towers for spotting this.
Replace m = p n 2 by c m = p n 2 (three separate times).
Thanks to Francisco Lieberich for spotting this.
It is x
that is a doubly-linked list, not xs
.
Thanks to Nobuo Yamashita and Peter Salvi for spotting this.
Missing closing parenthesis at the end of the line.
Thanks to Carlos Suberviola Oroz and Francisco Lieberich for spotting this.
Redundant curly bracket on the left-hand side.
Thanks to Peter Salvi, Carlos Suberviola Oroz, Francisco Lieberich, and Matthew Towers for spotting this.
This is the first occurrence of foldl1
; perhaps it should have been introduced on p121 along with foldr1
.
Thanks to Francisco Lieberich for spotting this.
It's R.W. Hamming, not W.R. Hamming.
Thanks to Francisco Lieberich for spotting this.
It should be x
that is compared with head ys
, not xs
.
Thanks to Francisco Lieberich and Matthew Towers for spotting this.
The proof sketch is wrong; for example, there's no easy way to obtain
crs 3 = 4:6:8:9:10:12:14:15:16:18:20:21:22:24:25:undefinedfrom
crs 2 = 4:6:8:9:undefinedand
(let p = 5 in map (p*) [p..]) = [25,30..]
Thanks to Francisco Lieberich for spotting this. Jeremy Gibbons has blogged about this. In fact, crs 3
can be obtained from crs 2
alone…
The second block of code should read
do {y <- lookup x alist; z <- lookup y blist; lookup z clist}without the
return
.
Thanks to Randall Britten for spotting this.
Type vs. value:
... and in the expression runST (newSTRef True)
the Haskell type checker ...
Thanks to Torsten Grust for spotting this.
The definition should read:
sort xs = concat [ replicate c x | (x,c) <- assocs (count xs) ]
Thanks to Mani Tadayon for spotting this.
The proof obligation is:
foldr (\ n p -> add n >> p) done = add . foldr (+) 0
Thanks to Matthew Towers for spotting this.
The text "parser q
" should read "parser q x
". Also, as of GHC 7.10, it is necessary to make Parser
also an instance of Functor
and Applicative
in order to make it a Monad
.
Thanks to Matthew Towers for spotting this.
The type of guard
is Bool -> Parser ()
.
Thanks to Zhe Zhang for spotting this.
Definition of showParen
:
showParen b p = if b then...
Thanks to Torsten Grust for spotting this.
Invocation of showParen
in the definition of shows
:
shows b (Bin op e1 e2) = = showParen b (shows ...)
Thanks to Torsten Grust for spotting this.
The proposed definition of <|>
should use apply
rather than parse
:
p <|> q = Parser (\ s -> apply p s ++ apply q s)
Thanks to Dimitris Orfanos for spotting this.
The definition of bind is broken, for several reasons. The answer should be like this:
p >>= q = Parser (\ s -> case apply p s of Nothing -> Nothing Just (x,s') -> apply (q x) s')(Note that we also need a different definition of
apply
, because of the different definition of the datatype Parser
.)
Thanks to Dimitris Orfanos and Nicolas Del Piano for spotting this.
first
vs. fst
in a law: fst
after fork
: fst . fork f g = f
Thanks to Torsten Grust for spotting this.
Expression representation:
(f * g) . h => Compose [Con "*" [Compose [Var "f"], Compose [Var "g"]], Var "h"]
Thanks to Torsten Grust for spotting this.
Type name:
ident :: Parser [Expr] -> Parser Expr
Thanks to Torsten Grust for spotting this.
The third equation for xmatchA
is missing the sub
argument.
Thanks to Paul Horsfall for spotting this.
RetroSearch is an open source project built by @garambo | Open a GitHub Issue
Search and Browse the WWW like it's 1997 | Search results from DuckDuckGo
HTML:
3.2
| Encoding:
UTF-8
| Version:
0.7.4