[GHC] #5429: Docase notation as GHC extension

GHC ghc-devs at haskell.org
Thu Oct 22 13:47:00 UTC 2015


#5429: Docase notation as GHC extension
-------------------------------------+-------------------------------------
        Reporter:  tomasp            |                Owner:  tomasp
            Type:  feature request   |               Status:  closed
        Priority:  normal            |            Milestone:  8.0.1
       Component:  Compiler          |              Version:
      Resolution:  wontfix           |             Keywords:  monad,
                                     |  syntactic sugar, mzip,
                                     |  comprehensions
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by bgamari):

 * status:  new => closed
 * resolution:   => wontfix


Old description:

> Many monads provide additional combinators for ''parallel composition'',
> ''choice'' and ''aliasing''. In our Haskell Symposium 2011 paper
> (http://www.cl.cam.ac.uk/~tp322/papers/docase.html) we call a monad with
> these 3 additional combinators a '''joinad'''.
>
> The monads that implement (some of) these three operations include:
>
>   * '''Par monad''' for parallel programming implements ''parallel
> composition'' (run two computations in parallel) and ''aliasing'' (start
> computation and access the result in multiple other computations) and can
> be extended to support (non-deterministic) ''choice''
>   * '''Parsers''' can implement ''parallel composition'' as an
> intersection of languages (parse the same input using multiple parsers),
> which is useful for encoding validation rules and ''choice'' (use the
> result of a first parser that succeeds).
>   * '''Other monads''' that can be considered include the `Orc` monad
> (for concurrent orchestration) and the encoding of CHP (Communicating
> Haskell Processes).
>
> The proposal is to implement the a GHC extension that allows the `docase`
> notation for working with ''joinads''. Using the `Par` monad as an
> example, the following snippet implements a function `all` which tests
> whether a predicate holds for all leaves of a tree:
>
> {{{
> all :: (a -> Bool) -> Tree a -> Par Bool
>
> all p (Leaf v)           = return (p v)
> all p (Node left right)  =
>   docase all p left, all p right of
>     False, ?    -> return False
>     ?, False    -> return False
>     allL, allR  -> return (allL && allR)
> }}}
>
> The left and right sub-trees are processed in parallel (using ''parllel
> composition''). The special pattern `?` denotes that the corresponding
> computation does not have to complete in order for the clause to match.
> This means that the first two clauses implement short-circuiting behavior
> (and can match even if the other branch is still being processed).
>
> The operations used by the desugaring are expected to have the following
> types:
>
>  * `mzip :: m a -> m b -> m (a, b)`[[br]]This operation has been added by
> the recent patch that re-implements ''monad comprehensions'', so we can
> reuse it.
>  * `morelse :: m a -> m a -> m a`[[br]]The operation has the same type as
> `mplus` from `MonadPlus`, but we require an operation that is left-
> biased. One possible option is to add `MonadOr` type class as suggested
> in http://www.haskell.org/haskellwiki/MonadPlus_reform_proposal.
>  * `malias :: m a -> m (m a)`[[br]]The operation "starts" a computation
> and returns a handle for accessing the result. It has been used e.g. by
> the authors of the `Orc` monad. For many simpler monads, this can be
> implemented as monadic `return`.
>
> ==Feedback==
>
> I would appreciate any feedback from GHC users and developers! In
> particular, here are some general, as well as more specific questions
> that I've heard in the past:
>
>  * What existing monads can implement the interface? (I believe there are
> quite a few of them including `Par`, Parsers, `Orc`, CPH, but I'd love to
> know about more.)
>
>  * What to do about monads that implement only some operations?
> Currently, the `malias` operation has default implementation. If a
> `docase` notation has just a single clause, then `morelse` is not
> required. If it has multiple clauses, each having just a single ''binding
> pattern'' (non `?`) then `mzip` is not required.
>
>  * The laws - the paper includes detailed discussion about laws (e.g. why
> `mzip` should be symmetric and why `morelse` should have left-biase).
> Does the community agree with the laws, or do you suggest some changes?
>
>  * Syntax seems to be a tricky question - the notation intentionally
> resembles `case`, but it takes a list of arguments (of type `m a1`, ...,
> `m an`), so it is not using ''tuple syntax''. Is there any better
> alternative?
>
>  * Correspondence with ''monad comprehensions'' - the `docase` notation
> can express parallel composition in a similar way as ''monad
> comprehensions''. I think this parity is a good thing. However, it allows
> more expressivity in one direction (by adding choice) and less in another
> (no group/order by comprehensions). Do you think this is a good ballance?

New description:

 Many monads provide additional combinators for ''parallel composition'',
 ''choice'' and ''aliasing''. In our Haskell Symposium 2011 paper
 (http://www.cl.cam.ac.uk/~tp322/papers/docase.html) we call a monad with
 these 3 additional combinators a '''joinad'''.

 The monads that implement (some of) these three operations include:

   * '''Par monad''' for parallel programming implements ''parallel
 composition'' (run two computations in parallel) and ''aliasing'' (start
 computation and access the result in multiple other computations) and can
 be extended to support (non-deterministic) ''choice''
   * '''Parsers''' can implement ''parallel composition'' as an
 intersection of languages (parse the same input using multiple parsers),
 which is useful for encoding validation rules and ''choice'' (use the
 result of a first parser that succeeds).
   * '''Other monads''' that can be considered include the `Orc` monad (for
 concurrent orchestration) and the encoding of CHP (Communicating Haskell
 Processes).

 The proposal is to implement the a GHC extension that allows the `docase`
 notation for working with ''joinads''. Using the `Par` monad as an
 example, the following snippet implements a function `all` which tests
 whether a predicate holds for all leaves of a tree:

 {{{
 all :: (a -> Bool) -> Tree a -> Par Bool

 all p (Leaf v)           = return (p v)
 all p (Node left right)  =
   docase all p left, all p right of
     False, ?    -> return False
     ?, False    -> return False
     allL, allR  -> return (allL && allR)
 }}}

 The left and right sub-trees are processed in parallel (using ''parllel
 composition''). The special pattern `?` denotes that the corresponding
 computation does not have to complete in order for the clause to match.
 This means that the first two clauses implement short-circuiting behavior
 (and can match even if the other branch is still being processed).

 The operations used by the desugaring are expected to have the following
 types:

  * `mzip :: m a -> m b -> m (a, b)`[[br]]This operation has been added by
 the recent patch that re-implements ''monad comprehensions'', so we can
 reuse it.
  * `morelse :: m a -> m a -> m a`[[br]]The operation has the same type as
 `mplus` from `MonadPlus`, but we require an operation that is left-biased.
 One possible option is to add `MonadOr` type class as suggested in
 http://www.haskell.org/haskellwiki/MonadPlus_reform_proposal.
  * `malias :: m a -> m (m a)`[[br]]The operation "starts" a computation
 and returns a handle for accessing the result. It has been used e.g. by
 the authors of the `Orc` monad. For many simpler monads, this can be
 implemented as monadic `return`.

 == Feedback ==

 I would appreciate any feedback from GHC users and developers! In
 particular, here are some general, as well as more specific questions that
 I've heard in the past:

  * What existing monads can implement the interface? (I believe there are
 quite a few of them including `Par`, Parsers, `Orc`, CPH, but I'd love to
 know about more.)

  * What to do about monads that implement only some operations? Currently,
 the `malias` operation has default implementation. If a `docase` notation
 has just a single clause, then `morelse` is not required. If it has
 multiple clauses, each having just a single ''binding pattern'' (non `?`)
 then `mzip` is not required.

  * The laws - the paper includes detailed discussion about laws (e.g. why
 `mzip` should be symmetric and why `morelse` should have left-biase). Does
 the community agree with the laws, or do you suggest some changes?

  * Syntax seems to be a tricky question - the notation intentionally
 resembles `case`, but it takes a list of arguments (of type `m a1`, ...,
 `m an`), so it is not using ''tuple syntax''. Is there any better
 alternative?

  * Correspondence with ''monad comprehensions'' - the `docase` notation
 can express parallel composition in a similar way as ''monad
 comprehensions''. I think this parity is a good thing. However, it allows
 more expressivity in one direction (by adding choice) and less in another
 (no group/order by comprehensions). Do you think this is a good balance?

--

Comment:

 tomasp, I'm going to close this due to inactivity but feel free to reopen
 with a Phabricator Diff if you still want to see this happen.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/5429#comment:13>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list