Different choice operations in a continuation monad

Dear Café, `MonadPlus` instances are usually required to satisfy certain laws, among them the monad laws and monoid laws for `mzero` and `mplus`. Additionally one may require that (>>=f) is a monoid morphism, that is: mzero >>= f = mzero (a `mplus` b) >>= f = (a >>= f) `mplus` (b >>= f) The list monad satisfies these additional laws, the `Maybe`-Monad does not satisfy the second, distributive, law: ghci> (return False `mplus` return True) >>= guard :: [()] [()] ghci> (return False `mplus` return True) >>= guard :: Maybe () Nothing Instead of the distributive law, the `Maybe` monad satisfies a different law: return x `mplus` a = return x that is, `return` annihilates the `Maybe`-Monad regarding `mplus`. This "cancellation law" is incompatible with the distributive law because (together with other laws) it implies that the result of the above example expression is `Nothing` whereas the distributive law implies that it is `Just ()`. We can lift the `Maybe` type into a continuation monad:
newtype CMaybe r a = CMaybe ((a -> Maybe r) -> Maybe r)
instance Monad (CMaybe r) where return x = CMaybe (\k -> k x) CMaybe ca >>= f = CMaybe (\k -> ca (\x -> let CMaybe cb = f x in cb k))
instance MonadPlus (CMaybe r) where mzero = CMaybe (\_ -> mzero) CMaybe ca `mplus` CMaybe cb = CMaybe (\k -> ca k `mplus` cb k)
Unlike the `Maybe`-monad, the `CMaybe`-monad satisfies the distributive law, not the cancellation law. Can you define an associative operation orElse :: CMaybe r a -> CMaybe r a -> CMaybe r a with identity `mzero` that satisfies the cancellation law? Cheers, Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Hi Sebastian, Am 15.06.2010 um 17:06 schrieb Sebastian Fischer:
Dear Café,
`MonadPlus` instances are usually required to satisfy certain laws, among them the monad laws and monoid laws for `mzero` and `mplus`. Additionally one may require that (>>=f) is a monoid morphism, that is:
mzero >>= f = mzero (a `mplus` b) >>= f = (a >>= f) `mplus` (b >>= f)
The list monad satisfies these additional laws, the `Maybe`-Monad does not satisfy the second, distributive, law:
ghci> (return False `mplus` return True) >>= guard :: [()] [()] ghci> (return False `mplus` return True) >>= guard :: Maybe () Nothing
Instead of the distributive law, the `Maybe` monad satisfies a different law:
return x `mplus` a = return x
that is, `return` annihilates the `Maybe`-Monad regarding `mplus`. This "cancellation law" is incompatible with the distributive law because (together with other laws) it implies that the result of the above example expression is `Nothing` whereas the distributive law implies that it is `Just ()`.
We can lift the `Maybe` type into a continuation monad:
newtype CMaybe r a = CMaybe ((a -> Maybe r) -> Maybe r)
instance Monad (CMaybe r) where return x = CMaybe (\k -> k x) CMaybe ca >>= f = CMaybe (\k -> ca (\x -> let CMaybe cb = f x in cb k))
instance MonadPlus (CMaybe r) where mzero = CMaybe (\_ -> mzero) CMaybe ca `mplus` CMaybe cb = CMaybe (\k -> ca k `mplus` cb k)
Unlike the `Maybe`-monad, the `CMaybe`-monad satisfies the distributive law, not the cancellation law.
Can you define an associative operation
orElse :: CMaybe r a -> CMaybe r a -> CMaybe r a
with identity `mzero` that satisfies the cancellation law?
No, because that function would need to cancel values of type a, but the arguments of type (CMaybe r a) can only compute values of type r. But you can define orElse :: CMaybe a a -> CMaybe a a -> CMaybe r a CMaybe ca `orElse` CMaybe cb = CMaybe (\k -> (ca return `mplus` cb return) >>= k)

Hello Holger,
Can you define an associative operation
orElse :: CMaybe r a -> CMaybe r a -> CMaybe r a
with identity `mzero` that satisfies the cancellation law?
No, because that function would need to cancel values of type a, but the arguments of type (CMaybe r a) can only compute values of type r.
I'm afraid, I don't understand.
But you can define
orElse :: CMaybe a a -> CMaybe a a -> CMaybe r a CMaybe ca `orElse` CMaybe cb = CMaybe (\k -> (ca return `mplus` cb return) >>= k)
Good point. But with this restricted type `orElse` is less useful. For example, one cannot compute fromCMaybe ((return False `orElse` return True) >>= guard) because there, the arguments of `orElse` are of type `CMaybe () Bool`. Cheers, Sebastian P.S.
fromCMaybe :: CMaybe a a -> Maybe a fromCMaybe (CMaybe ca) = ca Just
-- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

On Jun 15, 2010, at 6:11 PM, Sebastian Fischer wrote:
orElse :: CMaybe a a -> CMaybe a a -> CMaybe r a CMaybe ca `orElse` CMaybe cb = CMaybe (\k -> (ca return `mplus` cb return) >>= k)
Good point.
But with this restricted type `orElse` is less useful. For example, one cannot compute
fromCMaybe ((return False `orElse` return True) >>= guard)
because there, the arguments of `orElse` are of type `CMaybe () Bool`.
Silly me! It's not the type of the *arguments* which is `CMaybe () Bool` but the type of the *result* of `orElse`, which is perfectly possible with your implementation! The type may be general enough. Interesting twist! I still don't understand why it is impossible to provide `orElse` with the original type. I will think more about the reason you gave. Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Sebastian Fischer wrote:
Holger Siegel wrote:
orElse :: CMaybe a a -> CMaybe a a -> CMaybe r a CMaybe ca `orElse` CMaybe cb = CMaybe (\k -> (ca return `mplus` cb return) >>= k)
I still don't understand why it is impossible to provide `orElse` with the original type. I will think more about the reason you gave.
The reason is that you have chosen the "wrong" type for your continuation monad; it should be newtype CMaybe a = CMaybe (forall r. (a -> Maybe r) -> Maybe r) Personally, I recommend to stop thinking about continuations altogether and instead use the approach I've outlined in "The Operational Monad Tutorial" http://apfelmus.nfshost.com/articles/operational-monad.html to define and think about monads. In particular, performing the refunctionalization I mentioned in the subsection "Connection with the Continuation Monad" shows that the "right" type should indeed contain a forall r . Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Heinrich Apfelmus wrote:
Sebastian Fischer wrote:
I still don't understand why it is impossible to provide `orElse` with the original type. I will think more about the reason you gave.
The reason is that you have chosen the "wrong" type for your continuation monad; it should be
newtype CMaybe a = CMaybe (forall r. (a -> Maybe r) -> Maybe r)
Yes, with this type `orElse` has the same type as `mplus`, which is very nice. <Aside>
Personally, I recommend to stop thinking about continuations altogether and instead use the approach I've outlined in "The Operational Monad Tutorial"
I appreciate your operational monad tutorial both for the idea and how you explained it. But the advice "stop thinking about X because Y is better" feels odd to me. Before I know by myself that Y is better than X (which requires thinking about both X and Y) I don't feel comfortable following such advice. Afterwards, I don't need such advice ;) There may be more to X than just Y. IIRC, there is more to 'continuations' than 'monads'. For example, the implementation of `callCC` does not type check with your changed data type. </Aside> I shall try to implement a monad that supports two choice operations (one which fulfills the distributive law and one which satisfies the cancellation property) with the operational package. Cheers, Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Sebastian Fischer wrote:
Heinrich Apfelmus wrote:
The reason is that you have chosen the "wrong" type for your continuation monad; it should be
newtype CMaybe a = CMaybe (forall r. (a -> Maybe r) -> Maybe r)
Yes, with this type `orElse` has the same type as `mplus`, which is very nice.
<Aside>
Personally, I recommend to stop thinking about continuations altogether and instead use the approach I've outlined in "The Operational Monad Tutorial"
I appreciate your operational monad tutorial both for the idea and how you explained it. But the advice "stop thinking about X because Y is better" feels odd to me. Before I know by myself that Y is better than X (which requires thinking about both X and Y) I don't feel comfortable following such advice. Afterwards, I don't need such advice ;)
Very true. :) My flimsy "personally" was an attempt to declare my recommendation optional. I failed to say the right thing even then, for I don't mean to stop thinking about continuations in general, just to discourage them as foundation for implementing other monads.
There may be more to X than just Y. IIRC, there is more to 'continuations' than 'monads'. For example, the implementation of `callCC` does not type check with your changed data type.
Ah, indeed, callCC in the operational setting is much trickier than I thought. However, it also seems to be the reason why your original approach does not work so well! Basically, your choice of implementation newtype CMaybe r a = CMaybe ((a -> Maybe r) -> Maybe r) supplies a default semantics for callCC . But this means that when implementing orElse , you also have to consider its interaction with callCC , even when you actually don't want to expose or implement a callCC function. As for the interaction: what should ((callCC ($ 0) >> mzero) `orElse` return 2) >>= return . (+3) be? If the scope of callCC should not extend past orElse , then this evaluates to return 5 . But this choice of scope dictates the type that Holger mentioned. If the the scope of callCC should extend beyond the orElse , so that the whole thing evaluates to mzero , orElse will have the type of mplus . But then, I think that your implementation type CMaybe needs to be more sophisticated because orElse now needs to detect whether the argument contains a call to callCC or not in order to distinguish ((callCC ($ 0) >> mzero) `orElse` return 2) >>= return . (+3) ==> mzero from (mzero `orElse` return 2) >>= return . (+3) ==> return 5 In short, the interaction between orElse and callCC is tricky, and it would be unfortunate to be forced to consider it due to a premature choice of implementation type. This can't happen with the operational approach, because that one merely implements the "free" monad over a set of operations.
I shall try to implement a monad that supports two choice operations (one which fulfills the distributive law and one which satisfies the cancellation property) with the operational package.
The main task will probably be to figure out the interaction between mplus and orElse , i.e. to consider what stuff like a `orElse` (b `mplus` c) should evaluate to. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Heinrich Apfelmus wrote:
Sebastian Fischer wrote:
For example, the implementation of `callCC` does not type check with your changed data type.
[snip]
As for the interaction: what should
((callCC ($ 0) >> mzero) `orElse` return 2) >>= return . (+3)
be? If the scope of callCC should not extend past orElse , then this evaluates to return 5 . But this choice of scope dictates the type that Holger mentioned.
If the the scope of callCC should extend beyond the orElse , so that the whole thing evaluates to mzero , orElse will have the type of mplus . But then, I think that your implementation type CMaybe needs to be more sophisticated because orElse now needs to detect whether the argument contains a call to callCC or not in order to distinguish
((callCC ($ 0) >> mzero) `orElse` return 2) >>= return . (+3)
==> mzero
from
(mzero `orElse` return 2) >>= return . (+3)
==> return 5
Out of curiosity, I've implemented these semantics with operational . Code attached. Took me a while to figure out how to implement callCC , but it turns out to be straightforward if you simply carry around the current continuation as an additional parameter. It doesn't seem to be possible to implement this with just the CMaybe r a type, in particular since the implementation I gave cannot be refunctionalized to said type. In other words, there is probably no associative operation orElse :: CMaybe r a -> CMaybe r a -> CMaybe r a with identity `mzero` that satisfies the cancellation law. I don't have a proof, but the argument that it doesn't interact well with the default implementation of callCC seems strong to me. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Wed, Jun 16, 2010 at 9:11 AM, Sebastian Fischer < sebf@informatik.uni-kiel.de> wrote:
Heinrich Apfelmus wrote:
Sebastian Fischer wrote:
I still don't understand why it is impossible to provide `orElse` with the original type. I will think more about the reason you gave.
The reason is that you have chosen the "wrong" type for your continuation monad; it should be
newtype CMaybe a = CMaybe (forall r. (a -> Maybe r) -> Maybe r)
Yes, with this type `orElse` has the same type as `mplus`, which is very nice.
This type is the same as "Codensity Maybe" using category-extras which is a 'bit bigger than Maybe'. (To see why, figure out how Codensity Reader is isomorphic to State!) This is the wiggle room you're using to get the distributive operator. Another encoding of Maybe is through Yoneda Endo newtype YEMaybe a = YEMaybe (forall r. (a -> r) -> r -> r) and it is isomorphic to the original Maybe type, with its same limitations. A definition that is equivalent to this is in my monad-ran package, along with definitions CPS/right-kan-extension-based definitions for other common monads, including the MTL, IO, ST s, and STM. -Edward Kmett

Edward Kmett wrote:
Sebastian Fischer wrote: Heinrich Apfelmus wrote: newtype CMaybe a = CMaybe (forall r. (a -> Maybe r) -> Maybe r) Yes, with this type `orElse` has the same type as `mplus`, which is very nice.
This type is the same as "Codensity Maybe" using category-extras which is a 'bit bigger than Maybe'. (To see why, figure out how Codensity Reader is isomorphic to State!) This is the wiggle room you're using to get the distributive operator.
I encounter the Codensity type constructor every now and then. I used it to Reinvent Haskell Backtracking, learned about implementing a state monad with a reader monad wrapped in Codensity when implementing Lazy Nondeterministic Programming and Janis Voigtländer also used it to improve the asymptotics of free monads. I wonder whether for every monad `m` and `a :: Codensity m a` getCodensity a f = getCodensity a return >>= f Is this true? Why (not)?
Another encoding of Maybe is through Yoneda Endo
Interesting. I did not yet encounter Yoneda in my own code but will watch out in the future. Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Sebastian Fischer wrote:
Edward Kmett wrote:
Sebastian Fischer wrote:
Heinrich Apfelmus wrote: newtype CMaybe a = CMaybe (forall r. (a -> Maybe r) -> Maybe r) Yes, with this type `orElse` has the same type as `mplus`, which is very nice.
This type is the same as "Codensity Maybe" using category-extras which is a 'bit bigger than Maybe'. (To see why, figure out how Codensity Reader is isomorphic to State!) This is the wiggle room you're using to get the distributive operator.
I encounter the Codensity type constructor every now and then. I used it to Reinvent Haskell Backtracking, learned about implementing a state monad with a reader monad wrapped in Codensity when implementing Lazy Nondeterministic Programming and Janis Voigtländer also used it to improve the asymptotics of free monads.
I wonder whether for every monad `m` and `a :: Codensity m a`
getCodensity a f = getCodensity a return >>= f
Is this true? Why (not)?
It's not true. a = Codensity $ \x -> Just 42 f = return . (+1) getCodensity a f = Just 42 ≠ getCodensity a return >>= f = Just 42 >>= f = Just 43 It probably is true if a is only built from >>= , return and actions from the original monad, though. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Fri, Jun 18, 2010 at 12:44 PM, Heinrich Apfelmus
Sebastian Fischer wrote:
Edward Kmett wrote:
Sebastian Fischer wrote:
Heinrich Apfelmus wrote: newtype CMaybe a = CMaybe (forall r. (a -> Maybe r) -> Maybe r) Yes, with this type `orElse` has the same type as `mplus`, which is very nice.
This type is the same as "Codensity Maybe" using category-extras which is a 'bit bigger than Maybe'. (To see why, figure out how Codensity Reader is isomorphic to State!) This is the wiggle room you're using to get the distributive operator.
I encounter the Codensity type constructor every now and then. I used it to Reinvent Haskell Backtracking, learned about implementing a state monad with a reader monad wrapped in Codensity when implementing Lazy Nondeterministic Programming and Janis Voigtländer also used it to improve the asymptotics of free monads.
I wonder whether for every monad `m` and `a :: Codensity m a`
getCodensity a f = getCodensity a return >>= f
Is this true? Why (not)?
It's not true.
a = Codensity $ \x -> Just 42 f = return . (+1)
getCodensity a f = Just 42 ≠ getCodensity a return >>= f = Just 42 >>= f = Just 43
What definition are you using for Codensity? Under the definition I'm
familiar with, that definition of a is invalid.
newtype Codensity m a = Codensity { runCodensity :: forall b. (a -> m
b) -> m b }
Which is not to say that you can't come up with improper values of
Codensity. E.g.,
Codensity (\k -> k () >> k ())
\m -> Codensity (\k -> k () >>= \b -> m >> return b)
--
Dave Menendez

David Menendez wrote:
Heinrich Apfelmus wrote:
Sebastian Fischer wrote:
I wonder whether for every monad `m` and `a :: Codensity m a`
getCodensity a f = getCodensity a return >>= f
Is this true? Why (not)?
It's not true.
a = Codensity $ \x -> Just 42 f = return . (+1)
getCodensity a f = Just 42 ≠ getCodensity a return >>= f = Just 42 >>= f = Just 43
What definition are you using for Codensity? Under the definition I'm familiar with, that definition of a is invalid.
Oops, silly me! I was thinking of Codensity r a = Codensity ((a -> m r) -> m r) which is wrong, of course.
newtype Codensity m a = Codensity { runCodensity :: forall b. (a -> m b) -> m b }
Which is not to say that you can't come up with improper values of Codensity. E.g.,
Codensity (\k -> k () >> k ())
\m -> Codensity (\k -> k () >>= \b -> m >> return b)
An example that is not generic in the base monad m , i.e. that makes use of m = Maybe is a = Codensity $ \k -> k 0 `orElse` k 1 -- orElse on plain Maybe f n = if even n then Nothing else Just n runCodensity a f = Just 1 runCodensity a return >>= f = Just 0 >>= f = Nothing Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Jun 18, 2010, at 8:55 PM, Heinrich Apfelmus wrote:
I wonder whether for every monad `m` and `a :: Codensity m a`
getCodensity a f = getCodensity a return >>= f
Is this true? Why (not)?
It's not true.
What a pity!
An example that is not generic in the base monad m , i.e. that makes use of m = Maybe is
a = Codensity $ \k -> k 0 `orElse` k 1 -- orElse on plain Maybe f n = if even n then Nothing else Just n
runCodensity a f = Just 1 runCodensity a return >>= f = Just 0 >>= f = Nothing
Nice example. Consider the given Definitions of `CMaybe r a` with `fromCMaybe`, `mzero`, `mplus`, `orElse`, and additionally: toCMaybe :: Maybe a -> CMaybe r a toCMaybe a = CMaybe (\k -> a >>= k) getCMaybe :: CMaybe r a -> (a -> Maybe r) -> Maybe r getCMaybe (CMaybe a) = a Much to my surprise, your example lead me to the following inequations: a /= toCMaybe (fromCMaybe a) because for ``a = return False `mplus` return True`` we have getCMaybe a guard = Just () getCMaybe (toCMaybe (fromCMaybe a)) guard = Nothing Also: a /= mzero `orElse` a because for the same `a` we have getCMaybe a guard = Just () getCMaybe (mzero `orElse` a) guard = Nothing Also: a /= a `orElse` mzero because for the same `a` we have getCMaybe a guard = Just () getCMaybe (a `orElse` mzero) guard = Nothing Pretty unfortunate. `mzero` is neither a left nor a right identity of `orElse`.
Out of curiosity, I've implemented these semantics with operational . Code attached.
Thanks!
It doesn't seem to be possible to implement this with just the CMaybe r a type, in particular since the implementation I gave cannot be refunctionalized to said type. In other words, there is probably no associative operation
orElse :: CMaybe r a -> CMaybe r a -> CMaybe r a
with identity `mzero` that satisfies the cancellation law. I don't have a proof, but the argument that it doesn't interact well with the default implementation of callCC seems strong to me.
Is `mzero` an identity for `orElse` in your code or can we create a counter example like the one above? Can you add a distributive `mplus` to your code that would behave differently in the examples above? Cheers, Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Sebastian Fischer wrote:
Consider the given Definitions of `CMaybe r a` with `fromCMaybe`, `mzero`, `mplus`, `orElse`, and additionally:
toCMaybe :: Maybe a -> CMaybe r a toCMaybe a = CMaybe (\k -> a >>= k)
getCMaybe :: CMaybe r a -> (a -> Maybe r) -> Maybe r getCMaybe (CMaybe a) = a
Much to my surprise, your example lead me to the following inequations:
a /= toCMaybe (fromCMaybe a)
because for ``a = return False `mplus` return True`` we have
getCMaybe a guard = Just () getCMaybe (toCMaybe (fromCMaybe a)) guard = Nothing
Also:
a /= mzero `orElse` a
because for the same `a` we have
getCMaybe a guard = Just () getCMaybe (mzero `orElse` a) guard = Nothing
Also:
a /= a `orElse` mzero
because for the same `a` we have
getCMaybe a guard = Just () getCMaybe (a `orElse` mzero) guard = Nothing
Pretty unfortunate. `mzero` is neither a left nor a right identity of `orElse`.
The reason is that in this implementation, orElse evaluates mplus too early x `orElse` (return False `mplus` return True) = x `orElse` return False and does not keep track of the fact that mplus does not decide for an alternative until the very end.
Is `mzero` an identity for `orElse` in your code or can we create a counter example like the one above? Can you add a distributive `mplus` to your code that would behave differently in the examples above?
In my code, mzero is indeed an identity for orElse as can be seen from the definition of the case eval kk (OrElse n m :>>= k) = case (eval kk' . view) n of ... -> ... MZeroR -> (eval kk . view) (m >>= k) where n evaluates to MZeroR . It shouldn't be difficult to add a distributive mplus ; it's definitely straightforward if we drop callCC . The observation is any action can be brought into one of the forms mzero return a `mplus` return b `mplus` ... which corresponds to the list type [a] . This, in turn, can be used to define orElse via pattern matching on the first argument. a `orElse` b = case a of { mzero -> b ; _ -> a } With the standard type definitions, the interpreter reads interpret :: Program Language a -> Maybe a interpret = listToMaybe . eval . view -- evaluate to a normal form eval :: ProgramView Language a -> [a] eval (Return a :>>= k) = [a] eval (MZero :>>= k) = [] eval (MPlus n m :>>= k) = (eval . view) (n >>= k) ++ (eval . view) (m >>= k) eval (OrElse n m :>>= k) = case (eval . view) n of [] -> (eval . view) (m >>= k) xs -> concatMap (eval . view . k) xs The call pattern of this interpreter shows that you can implement your type as newtype CMaybe a = CMaybe { forall b . (a -> [b]) -> [b] } but, as I said, this type is not good way of thinking about it in my opinion. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

On Jun 19, 2010, at 1:48 PM, Heinrich Apfelmus wrote:
In my code, mzero is indeed an identity for orElse [...] The observation is any action can be brought into one of the forms
mzero return a `mplus` return b `mplus` ...
which corresponds to the list type [a] .
Ok that makes sense because the list types supports both a cancelling `orElse` and a distributive `mplus` with identity `mzero`.
[...] you can implement your type as
newtype CMaybe a = CMaybe { forall b . (a -> [b]) -> [b] }
Yes. For me it was interesting to see how far we get by wrapping `Maybe` in `Codensity`: we get more than `Maybe` but not as much as `[]`. Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Sebastian Fischer wrote:
Heinrich Apfelmus wrote:
[...] you can implement your type as
newtype CMaybe a = CMaybe { forall b . (a -> [b]) -> [b] }
Yes. For me it was interesting to see how far we get by wrapping `Maybe` in `Codensity`: we get more than `Maybe` but not as much as `[]`.
Well, you can implement it with Maybe as well, at the price of duplicated computations. The idea is that for the implementation of orElse , we're not interested in the full list of results, only in whether this list is empty or not. This leads to eval :: ProgramView Language a -> Maybe a eval (Return a :>>= k) = Just a eval (MZero :>>= k) = Nothing eval (MPlus n m :>>= k) = (eval . view) (n >>= k) `mplus` (eval . view) (m >>= k) eval (OrElse n m :>>= k) = case (eval . view) n of Nothing -> (eval . view) (m >>= k) Just _ -> (eval . view) (n >>= k) Thanks to lazy evaluation, this is not too inefficient, even. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com
participants (5)
-
David Menendez
-
Edward Kmett
-
Heinrich Apfelmus
-
Holger Siegel
-
Sebastian Fischer