Thompson Exercise 9.13

Hi, I am new to Haskell (and programming). Thompson's exercise 9.13 in *Craft of Functional Programming *gave me trouble. Searching the list archives, I saw people define init (xs), last (xs), and so on, in a variety of complex ways (using the Maybe monad, using fairly complex post-processing). This seems to be a hard problem for beginners; at least, it was rather hard for me. The problem is to define the Prelude functions *init* and *last* using * foldr*. After a while, I came up with: -- *Exercise 9.13*: Use foldr (f, s, xs) to give definitions of the prelude functions -- unzip, last, and init. -- Clearly, -- [(x, y), (x1, y1)] = (x, y) : (x1, y1) : ([], []) -- foldr f ([], []) ((x, y):(x1, y1):[]) = f (x, y) (f (x1, y1) ([], [])) -- Hence, f (x, y) (xs, ys) must equal (x:xs, y:ys) for any xs, ys. unzip :: [(a, b)] -> ([a], [b]) unzip xys = foldr f ([], []) xys where f :: (a, b) -> ([a], [b]) -> ([a], [b]) f (x, y) (xs, ys) = (x:xs, y:ys) *last* :: [a] -> a last xs = head $ foldr f [] xs where f :: a -> [a] -> [a] f x [] = [x] f x ys = ys ++ [x] *init* :: [a] -> [a] init xs = tail $ foldr f [] xs where f :: a -> [a] -> [a] f x [] = [x] f x (y:xs) = y : x : xs Now, these seemed to be hard questions. So, I have three questions: (1) are these correct? They work on test cases, and I *did* do some quick proofs. They seem okay. (2) Is there a way to eliminate the post-processing of the lists (i.e., *head* in *last* and *tail* in *init*)? (3) Why the complex answers in the list archives? Am I missing something?

On Wednesday 14 July 2010 20:55:17, dan portin wrote:
Hi,
I am new to Haskell (and programming). Thompson's exercise 9.13 in *Craft of Functional Programming *gave me trouble. Searching the list archives, I saw people define init (xs), last (xs), and so on, in a variety of complex ways (using the Maybe monad,
Using Maybe isn't really complex, and for the implementations I sort of remember, the fact that Maybe is a Monad didn't play a role.
using fairly complex post-processing). This seems to be a hard problem for beginners; at least, it was rather hard for me.
Yes, it's not easy before you're familiar with foldr. If you don't try too hard to avoid any post-processing, it's not incredibly hard, though.
The problem is to define the Prelude functions *init* and *last* using * foldr*. After a while, I came up with:
-- *Exercise 9.13*: Use foldr (f, s, xs) to give definitions of the prelude functions -- unzip, last, and init.
-- Clearly, -- [(x, y), (x1, y1)] = (x, y) : (x1, y1) : ([], [])
That last one is a typo, [(x,y),(x1,y1)] = (x,y) : (x1,y1) : []
-- foldr f ([], []) ((x, y):(x1, y1):[]) = f (x, y) (f (x1, y1) ([], [])) -- Hence, f (x, y) (xs, ys) must equal (x:xs, y:ys) for any xs, ys.
Yup.
unzip :: [(a, b)] -> ([a], [b]) unzip xys = foldr f ([], []) xys where f :: (a, b) -> ([a], [b]) -> ([a], [b]) f (x, y) (xs, ys) = (x:xs, y:ys)
However, this has a small problem, take 3 . fst $ unzip [(i,i+1) | i <- [0 .. ]] won't return with that definition of unzip. The reason is subtle, f (x,y) (xs,ys) = (x:xs,y:ys) must inspect its second argument to match it with the pattern (xs,ys). To do that, it must evaluate the nested call to f first. f (x,y) (f (x1,y1) ([],[])) ~> match (xs,ys) with f (x1,y1) ([],[]) ~> evaluate f (x1,y1) ([],[]) ~> match (xs,ys) with ([],[]) ~> matches ~> (x1:[], y1:[]) ~> matches ~> (x:x1:[], y:y1:[]) Thus it needs to traverse the entire list before it can start assembling the result. To avoid that, so the result can be assembled from the start of the list, you need to make the pattern match on the second argument lazy, f (x,y) ~(xs,ys) = (x:xs,y:ys) or f (x,y) p = (x : fst p, y : snd p) Now f (x,y) (f (x1,y1) ([],[])) ~> let (xs,ys) = f (x1,y1) ([],[]) in (x:xs, y:ys) and assembling the result starts immediately. The tilde on a pattern makes that pattern irrefutable, the passed argument is bound to the pattern immediately and it will only be deconstructed/evaluated when needed. It's sort of a "trust me, the argument will have that form, don't check it" message to the compiler/interpreter. Of course it will usually crash hard if the passed argument doesn't have the promised form. In this case, it can't crash very hard, because the type checker doesn't allow anything but a pair to be passed as an argument, and a pair can only be (blah, blub) or _|_ (bottom). But if you use a tilde-pattern for a multi-constructor type, you better get it right.
*last* :: [a] -> a last xs = head $ foldr f [] xs where f :: a -> [a] -> [a] f x [] = [x] f x ys = ys ++ [x]
last xs = head (reverse xs), yes, it's correct, but not very pretty. And not very efficient since it builds a left-associated nest of (++) applications and needs to pattern match to decide which branch to take. last (1:2:3:4:[]) ~> head $ foldr f [] (1:2:3:4:[]) ~> head $ f 1 (f 2 (f 3 (f 4 []))) ~> head $ f 1 (f 2 (f 3 [4])) ~> head $ f 1 (f 2 ([4] ++ [3])) ~> head $ f 1 (([4] ++ [3]) ++ [2]) ~> head $ ((([4] ++ [3]) ++ [2]) ++ [1] a) in the second branch of f, you don't actually need to concatenate, f x [] = [x] f _ ys = ys works too, but is faster. b) you can get much faster by delaying the pattern match, f x ys = (case ys of { [] -> x; y:_ -> y }) : []
*init* :: [a] -> [a] init xs = tail $ foldr f [] xs where f :: a -> [a] -> [a] f x [] = [x] f x (y:xs) = y : x : xs
Correct too, but again not very efficient since it has to find the last element and bubble it to the front. Much faster: import Data.Maybe (fromMaybe) init' :: [a] -> [a] init' = fromMaybe (error "init': empty list") . foldr f Nothing where f x mb = Just $ case mb of Just xs -> x:xs Nothing -> [] By delaying the pattern match on the Maybe until after the constructor is applied, we can start building the output with minimal delay (we only need to look whether there's a next list element to decide whether to cons it to the front or not).
Now, these seemed to be hard questions. So, I have three questions: (1) are these correct? They work on test cases, and I *did* do some quick proofs. They seem okay.
They are correct for finite lists, unzip and init above won't return on infinite lists (last shouldn't, so that's correct for infinite lists too). They are not, strictly speaking, correct for infinite lists. But that is way beyond beginner territory :)
(2) Is there a way to eliminate the post-processing of the lists (i.e., *head* in *last* and *tail* in *init*)?
Not in a clean way. Let us consider last first. Suppose we had last xs = foldr f z xs without post-processing. Since foldr f z [] = z and last [] = error "Prelude.last: empty list", we must have z = error "...". Now last (... x:[]) = x and foldr f z (... x:[]) = ... (f x z) So f x y = y if y is not error "..." and f x (error "...") = x, that means f would have to find out whether its second argument is a specific error and return its first argument in that case, otherwise its second argument. It's possible to do that, but very unclean. For init, the situation is similar, the value for the empty list case supplied to foldr must be an error and the combining function needs to know whether its second argument is an error and do things accordingly.
(3) Why the complex answers in the list archives? Am I missing something?
Don't know. In part, because beginners didn't find the easiest ways, I suppose, in part because it's not too easy to give efficient implementations with foldr.

[...] it needs to traverse the entire list before it can start assembling the result. To avoid that, so the result can be assembled from the start of the list, you need to make the pattern match on the second argument lazy,
f (x,y) ~(xs,ys) = (x:xs,y:ys)
or
f (x,y) p = (x : fst p, y : snd p)
Now
f (x,y) (f (x1,y1) ([],[])) ~> let (xs,ys) = f (x1,y1) ([],[]) in (x:xs, y:ys)
This makes sense. I didn't realize Haskell was doing this. Of course, that could be a downside to evaluating by hand on paper, where you often 'think lazily.' I assumed Haskell evaluated the expression in a similar way to your 'let ...' clause.
*last* :: [a] -> a last xs = head $ foldr f [] xs where f :: a -> [a] -> [a] f x [] = [x] f x ys = ys ++ [x]
last xs = head (reverse xs), yes, it's correct, but not very pretty. And not very efficient since it builds a left-associated nest of (++) applications and needs to pattern match to decide which branch to take.
last (1:2:3:4:[]) ~> head $ foldr f [] (1:2:3:4:[]) ~> head $ f 1 (f 2 (f 3 (f 4 []))) ~> head $ f 1 (f 2 (f 3 [4])) ~> head $ f 1 (f 2 ([4] ++ [3])) ~> head $ f 1 (([4] ++ [3]) ++ [2]) ~> head $ ((([4] ++ [3]) ++ [2]) ++ [1]
a) in the second branch of f, you don't actually need to concatenate,
f x [] = [x] f _ ys = ys
works too, but is faster.
b) you can get much faster by delaying the pattern match,
f x ys = (case ys of { [] -> x; y:_ -> y }) : []
Yes, nesting each element inside (++) operators was an oversight on my part. Your solution (a) is much cleaner, since head $ foldr f [] (1:2:3:[]) ~> head $ f 1 (f 2 (f 3 [])) ~> head $ f 1 (f 2 (3:[])) ~> head $ f 1 (3:[]) ~> head $ (3:[]) I'm confused about (b), however. I was under the impressionhttp://www.haskell.org/tutorial/patterns.htmlthat the pattern match f P1 ... P1N = E1 f P2 ... P2N = E2 is *semantically* equivalent to f x1 ... xn = case (x1, ..., xn) of { P1 ... P1n -> E1; P2 ... P2n -> E2}. Of course, "semantically equivalent" doesn't mean "as efficient." I don't understand whether the move from matching against '_ ys' to y:_ is supposed to make the definition of f more efficient to compute, or whether the use of case expressions is supposed to.
*init* :: [a] -> [a] init xs = tail $ foldr f [] xs where f :: a -> [a] -> [a] f x [] = [x] f x (y:xs) = y : x : xs
Correct too, but again not very efficient since it has to find the last element and bubble it to the front.
Much faster: : import Data.Maybe (fromMaybe)
init' :: [a] -> [a] init' = fromMaybe (error "init': empty list") . foldr f Nothing where f x mb = Just $ case mb of Just xs -> x:xs Nothing -> []
By delaying the pattern match on the Maybe until after the constructor is applied, we can start building the output with minimal delay (we only need to look whether there's a next list element to decide whether to cons it to the front or not).
I'm not sure what you mean by "applying the constructor [Just]," or which function you are forcing to evaluate (after 'applying the constructor'). Obviously, I need to learn more about Haskell's monads and type constructors.
(2) Is there a way to eliminate the post-processing of the lists (i.e., *head* in *last* and *tail* in *init*)?
Not in a clean way.
Let us consider last first.
Suppose we had
last xs = foldr f z xs
without post-processing. Since foldr f z [] = z and last [] = error "Prelude.last: empty list", we must have z = error "...". Now last (... x:[]) = x and foldr f z (... x:[]) = ... (f x z)
So f x y = y if y is not error "..." and f x (error "...") = x, that means f would have to find out whether its second argument is a specific error and return its first argument in that case, otherwise its second argument. It's possible to do that, but very unclean.
That's helpful. I was trying to *name* a list at a particular stage of construction, and it failed for just this reason.

On Thursday 15 July 2010 15:46:15, dan portin wrote:
[...] it needs to traverse the entire list before it can start assembling the result. To avoid that, so the result can be assembled from the start of the list, you need to make the pattern match on the second argument lazy,
f (x,y) ~(xs,ys) = (x:xs,y:ys)
or
f (x,y) p = (x : fst p, y : snd p)
Now
f (x,y) (f (x1,y1) ([],[])) ~> let (xs,ys) = f (x1,y1) ([],[]) in (x:xs, y:ys)
This makes sense. I didn't realize Haskell was doing this.
I said it was subtle :)
Of course, that could be a downside to evaluating by hand on paper, where you often 'think lazily.' I assumed Haskell evaluated the expression in a similar way to your 'let ...' clause.
Pattern matching is strict (if you're matching against a refutable pattern; matching a variable pattern or wildcard always succeeds, so no evaluation is ever necessary then). Another way to achieve the same is f (x,y) p = let (xs,ys) = p in (x:xs, y:ys) Patterns bound in a let-expression or where-clause have an implicit ~, so a potential pattern-match failure is only reported when you're demanding a bound value which isn't there: Prelude> let foo x mb = let Just xs = mb in Just (x:xs) Prelude> foo True Nothing Just [True*** Exception: <interactive>:1:19-30: Irrefutable pattern failed for pattern Data.Maybe.Just xs
*last* :: [a] -> a last xs = head $ foldr f [] xs where f :: a -> [a] -> [a] f x [] = [x] f x ys = ys ++ [x]
last xs = head (reverse xs), yes, it's correct, but not very pretty. And not very efficient since it builds a left-associated nest of (++) applications and needs to pattern match to decide which branch to take.
last (1:2:3:4:[]) ~> head $ foldr f [] (1:2:3:4:[]) ~> head $ f 1 (f 2 (f 3 (f 4 []))) ~> head $ f 1 (f 2 (f 3 [4])) ~> head $ f 1 (f 2 ([4] ++ [3])) ~> head $ f 1 (([4] ++ [3]) ++ [2]) ~> head $ ((([4] ++ [3]) ++ [2]) ++ [1]
a) in the second branch of f, you don't actually need to concatenate,
f x [] = [x] f _ ys = ys
works too, but is faster.
b) you can get much faster by delaying the pattern match,
f x ys = (case ys of { [] -> x; y:_ -> y }) : []
Yes, nesting each element inside (++) operators was an oversight on my part. Your solution (a) is much cleaner, since
head $ foldr f [] (1:2:3:[]) ~> head $ f 1 (f 2 (f 3 [])) ~> head $ f 1 (f 2 (3:[])) ~> head $ f 1 (3:[]) ~> head $ (3:[])
I'm confused about (b), however. I was under the impressionhttp://www.haskell.org/tutorial/patterns.htmlthat the pattern match
f P1 ... P1N = E1 f P2 ... P2N = E2
is *semantically* equivalent to
f x1 ... xn = case (x1, ..., xn) of { P1 ... P1n -> E1; P2 ... P2n -> E2}.
Of course, "semantically equivalent" doesn't mean "as efficient."
That's the one point. However, that's not the point here. It was late and very hot, so I didn't write it as clear as was desirable, the function in b) can also be written as f x ys = z : [] where z = case ys of [] -> x y:_ -> y I think that makes it more understandable, the point is that the constructor (:) is applied on the RHS before we look whether ys matches [] or (_:_). If we evaluate it for a short list: head $ foldr f [] (1:2:3:[]) ~> head $ f 1 (foldr f [] (2:3:[])) ~> head (z1 : []) where z1 = case foldr f [] (2:3:[]) of { [] -> 1; y:_ -> y } ~> z1 where z1 = case foldr f [] (2:3:[]) of { [] -> 1; y:_ -> y } ~> case foldr f [] (2:3:[]) of { [] -> 1; y:_ -> y } ~> case f 2 (foldr f [] (3:[])) of { [] -> 1; y:_ -> y } ~> case z2 : [] of { [] -> 1; y:_ -> y } where z2 = case foldr f [] (3:[]) of { [] -> 2; w:_ -> w } ~> z2 where z2 = case foldr f [] (3:[]) of { [] -> 2; w:_ -> w } ~> case foldr f [] (3:[]) of { [] -> 2; w:_ -> w } ~> case f 3 (foldr f [] []) of { [] -> 2; w:_ -> w } ~> case z3 : [] of { [] -> 2; w:_ -> w } where z3 = case foldr f [] [] of { [] -> 3; v:_ -> v } ~> z3 where z3 = case foldr f [] [] of { [] -> 3; v:_ -> v } ~> case foldr f [] [] of { [] -> 3; v:_ -> v } ~> case [] of { [] -> 3; v:_ -> v } ~> 3 We never have deep nesting, we always have progress looking at no more than two successive list elements and can let the start of the list be garbage collected almost immediately. Now with g x [] = [x] g _ ys = ys we get head $ foldr g [] (1:2:3:[]) ~> head $ g 1 (foldr g [] (2:3:[])) -- we don't know which branch to take for g 1 _, so we -- must evaluate foldr g [] (2:3:[]) to see ~> head $ g 1 (g 2 (foldr g [] (3:[]))) -- we don't know which branch to take for g 2 _, so ~> head $ g 1 (g 2 (g 3 (foldr g [] []))) -- we don't know which branch to take for g 3 _, so ~> head $ g 1 (g 2 (g 3 [])) ~> head $ g 1 (g 2 [3]) ~> head $ g 1 [3] ~> head $ [3] ~> 3 And you see that we get nested calls to g, the nesting depth is length list and we hold on to the start of the list until we can finally apply head. This doesn't require more reduction steps [both need O(length list) steps], but it requires O(length list) space vs O(1) space for the f above, hence this is much slower.
I don't understand whether the move from matching against '_ ys' to y:_ is supposed to make the definition of f more efficient to compute, or whether the use of case expressions is supposed to.
What makes it more efficient is that we start constructing the result before we investigate the arguments. Thus we can know which branch to take before we've reached the end of the list.
*init* :: [a] -> [a] init xs = tail $ foldr f [] xs where f :: a -> [a] -> [a] f x [] = [x] f x (y:xs) = y : x : xs
Correct too, but again not very efficient since it has to find the last element and bubble it to the front.
Much faster:
import Data.Maybe (fromMaybe)
init' :: [a] -> [a] init' = fromMaybe (error "init': empty list") . foldr f Nothing where f x mb = Just $ case mb of Just xs -> x:xs Nothing -> []
By delaying the pattern match on the Maybe until after the constructor is applied, we can start building the output with minimal delay (we only need to look whether there's a next list element to decide whether to cons it to the front or not).
I'm not sure what you mean by "applying the constructor [Just],"
Similar to the above, f x mb = Just zs where zs = case mb of Just xs -> x:xs Nothing -> [] By having the result Just something before we inspect the arguments, we can start building the result almost immediately, we only have to see whether the second argument comes from a call to f (in other words, whether there's at least one further element in the list) to know which branch to take. If we pattern match first, we again build a nest of applications of f until we reach the end of the list and can only then start to unwind the stack.
or which function you are forcing to evaluate (after 'applying the constructor'). Obviously, I need to learn more about Haskell's monads and type constructors.
Nothing to do with monads, it's all about laziness and pattern matching. As a general rule, in foldr fun z xs you want fun to be as lazy as possible in its second argument, i.e. do everything you can do before even looking at it. If you can even do something before looking at fun's first argument, all the better.
(2) Is there a way to eliminate the post-processing of the lists (i.e., *head* in *last* and *tail* in *init*)?
Not in a clean way.
Let us consider last first.
Suppose we had
last xs = foldr f z xs
without post-processing. Since foldr f z [] = z and last [] = error "Prelude.last: empty list", we must have z = error "...". Now last (... x:[]) = x and foldr f z (... x:[]) = ... (f x z)
So f x y = y if y is not error "..." and f x (error "...") = x, that means f would have to find out whether its second argument is a specific error and return its first argument in that case, otherwise its second argument. It's possible to do that, but very unclean.
That's helpful. I was trying to *name* a list at a particular stage of construction, and it failed for just this reason.

Hi,
*last* :: [a] -> a last xs = head $ foldr f [] xs where f :: a -> [a] -> [a] f x [] = [x] f x ys = ys ++ [x]
a) in the second branch of f, you don't actually need to concatenate,
f x [] = [x] f _ ys = ys
works too, but is faster.
Why is it faster? I thought that the laziness would cause the concatenation not to be evaluated at all since we are taking the head of the list. Is that not the case? Thanks, Patrick
b) you can get much faster by delaying the pattern match,
f x ys = (case ys of { [] -> x; y:_ -> y }) : []
*init* :: [a] -> [a] init xs = tail $ foldr f [] xs where f :: a -> [a] -> [a] f x [] = [x] f x (y:xs) = y : x : xs
Correct too, but again not very efficient since it has to find the last element and bubble it to the front.
Much faster:
import Data.Maybe (fromMaybe)
init' :: [a] -> [a] init' = fromMaybe (error "init': empty list") . foldr f Nothing where f x mb = Just $ case mb of Just xs -> x:xs Nothing -> []
By delaying the pattern match on the Maybe until after the constructor is applied, we can start building the output with minimal delay (we only need to look whether there's a next list element to decide whether to cons it to the front or not).
Now, these seemed to be hard questions. So, I have three questions: (1) are these correct? They work on test cases, and I *did* do some quick proofs. They seem okay.
They are correct for finite lists, unzip and init above won't return on infinite lists (last shouldn't, so that's correct for infinite lists too). They are not, strictly speaking, correct for infinite lists. But that is way beyond beginner territory :)
(2) Is there a way to eliminate the post-processing of the lists (i.e., *head* in *last* and *tail* in *init*)?
Not in a clean way.
Let us consider last first.
Suppose we had
last xs = foldr f z xs
without post-processing. Since foldr f z [] = z and last [] = error "Prelude.last: empty list", we must have z = error "...". Now last (... x:[]) = x and foldr f z (... x:[]) = ... (f x z)
So f x y = y if y is not error "..." and f x (error "...") = x, that means f would have to find out whether its second argument is a specific error and return its first argument in that case, otherwise its second argument. It's possible to do that, but very unclean.
For init, the situation is similar, the value for the empty list case supplied to foldr must be an error and the combining function needs to know whether its second argument is an error and do things accordingly.
(3) Why the complex answers in the list archives? Am I missing something?
Don't know. In part, because beginners didn't find the easiest ways, I suppose, in part because it's not too easy to give efficient implementations with foldr.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

On Thursday 15 July 2010 16:06:01, Patrick LeBoutillier wrote:
Hi,
*last* :: [a] -> a last xs = head $ foldr f [] xs where f :: a -> [a] -> [a] f x [] = [x] f x ys = ys ++ [x]
a) in the second branch of f, you don't actually need to concatenate,
f x [] = [x] f _ ys = ys
works too, but is faster.
Why is it faster? I thought that the laziness would cause the concatenation not to be evaluated at all since we are taking the head of the list. Is that not the case?
That is (almost) the case (otherwise the performance of the first version would be worse), but for each list element, the pattern match in the folded function forces one evaluation step of a (++)-application [and for that, one further pattern match], thus it has to do more work. Remember, [] ++ ys = ys (x:xs) ++ ys = x : (xs ++ ys) If we look at what happens with f1 x [] = [x] f1 x ys = ys ++ [x] in a generic step: f1 x (f1 y zs) ~> case f1 y zs of { [] -> [x]; w:ws -> (w:ws) ++ [x] } ~> case (case zs of { [] -> [y]; v:vs -> (v:vs) ++ [y] }) of { [] -> [x]; w:ws -> (w:ws) ++ [x] } -- let's assume zs is not null ~> case (v:vs) ++ [y] of { [] -> [x]; w:ws -> (w:ws) ++ [x] } ~> case (case (v:vs) of { [] -> [y]; u:us -> u:(us ++ [y]) }) of { [] -> [x]; w:ws -> (w:ws) ++ [x] } ~> case v:(vs ++ [y]) of { [] -> [x]; w:ws -> (w:ws) ++ [x] } ~> (v:(vs ++ [y])) ++ [x] and with f2 x [] = [x] f2 _ ys = ys f2 x (f2 y zs) ~> case f2 y zs of { [] -> [x]; w:ws -> (w:ws) } ~> case (case zs of { [] -> [y]; v:vs -> (v:vs) }) of { [] -> [x]; w:ws -> (w:ws) } -- again, assume zs is not null ~> case v:vs of { [] -> [x]; w:ws -> (w:ws) } ~> v:vs In the former, at each step, to determine the branch of f1, an expression of the form (us ++ vs) has to be matched against []. For that, us has to be matched against []. Typically, us is of the form (u:us'), so (us ++ vs) is rewritten to u:(us' ++ vs). That doesn't match [], so the second branch of f1 is taken and we get (u:(us' ++ vs)) ++ [x], again wrapping the first (:) in a (++)-application. For each list-element, we must evaluate a (++)-application one step. In the latter, once at the end of the list a (y:[]) is produced, all that happens is pattern matching and passing the value unmodified to the next pattern match.
Thanks,
Patrick
Cheers, Daniel
participants (3)
-
dan portin
-
Daniel Fischer
-
Patrick LeBoutillier