[Haskell-cafe] CoArbitrary

Tony Morris tonymorris at gmail.com
Sun Feb 10 09:33:45 CET 2013


On 09/02/13 15:08, Roman Cheplyaka wrote:
> I don't think the question was about generating functions...
> FWIW, both QuickCheck and SmallCheck generate functions. There was also
> an interesting paper at the last ICFP by Koen related to this.
>
> But I think Tony is looking for some kind of a pattern here...
>
> Roman
>
> * Stephen Tetley <stephen.tetley at gmail.com> [2013-02-09 10:50:45+0000]
>> I think GAST - the Clean equivalent of Quickcheck - generates
>> functions. There are certainly quite a few papers by members of the
>> Clean team documenting how they generate them.
>>
>> On 9 February 2013 07:07, Tony Morris <tonymorris at gmail.com> wrote:
>> [...]
>>> I hope I have phrased this in a way to make the point. I found it a bit
>>> difficult to articulate and I do wonder (hope!) that others encounter
>>> similar scenarios. Thanks for any tips!
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
Yeah I am looking for a possible pattern. I am struggling to explain the
problem. Perhaps some code will help.

This code compiles, however the function "problem" is the one I am
looking for. There are two data structures here:
1) Op, which is a functor
2) FreeOp, which is a monad that arises from the Op functor (i.e. an
instance of the free monad)

There are some functions for demonstration:
1) productOp -- An example of zipping two FreeOp instances, just to show
that you can (though, this is trivial by the monad)
2) booleanOp -- Produces a FreeOp Bool by using the IntOp constructor for Op
3) coproductOp -- An example of splitting out two FreeOp instances, to
show this is possible too.

* The question is, what about a function FreeOp b -> FreeOp (a -> b)?
* Can I constrain the 'a' type variable somehow to come up with
something similar to CoArbitrary (QuickCheck)?
* Can I generalise this idea i.e. not just FreeOp? Or for CoArbitrary,
not just for Gen?
* Is there a pattern here that is currently not part of my mental tool
kit? I am struggling to see it; maybe just it's not there.

As always, thanks for any pointers!

Begin code...


data Op a =
  DoubleOp (Double -> a)
  | IntOp (Int -> a)

data FreeOp a =
  Suspend (Op (FreeOp a))
  | Point a

---- examples

productOp ::
  FreeOp a
  -> FreeOp b
  -> FreeOp (a, b)
productOp a b =
  do a' <- a
     b' <- b
     return (a', b')

boolOp ::
  FreeOp Bool
boolOp =
  Suspend (fmap Point (IntOp even))

coproductOp ::
  FreeOp a
  -> FreeOp b
  -> FreeOp (Either a b)
coproductOp a b =
  boolOp >>= \p -> if p then fmap Left a else fmap Right b

---- The Problem

problem ::
  -- ? c =>
  -- ? other arguments
  FreeOp b
  -> FreeOp (a -> b)
problem =
  error "what constraints on 'a' to allow an implementation of this
function that uses the argument?"
  -- fmap const -- type-checks, but ignores the argument, unlike e.g.
QuickCheck which uses CoArbitrary to "perturb" that result with the
argument.

---- support libraries

instance Functor Op where
  fmap f (DoubleOp g) =
    DoubleOp (f . g)
  fmap f (IntOp g) =
    IntOp (f . g)

instance Functor FreeOp where
  fmap f =
    (=<<) (return . f)

instance Monad FreeOp where
  return =
    Point
  Suspend o >>= f =
    Suspend (fmap (>>= f) o)
  Point a >>= f =
    f a


-- 
Tony Morris
http://tmorris.net/




More information about the Haskell-Cafe mailing list