[Haskell-cafe] Trying to test natural transformations, in Haskell.

Carter Schonwald carter.schonwald at gmail.com
Sat Jun 18 15:18:33 UTC 2016


My rule of thumb is to also always have scoped type variables enabled in my
own code.


I also strongly advise against allow ambiguous types, it's seldom what you
want.

On Thursday, June 16, 2016, David Banas <capn.freako at gmail.com> wrote:

> Got it:
>
> {-# LANGUAGE Rank2Types
>              AllowAmbiguousTypes
>              FlexibleContexts
>   #-}
>
> type NatTran f f' a = (Functor f, Functor f') => f a -> f' a
>
> to_assert :: (Functor f, Functor f', Eq (f' b)) => (a -> b) -> NatTran f
> f' a -> NatTran f f' b -> f a -> Bool
> to_assert g h h' f = (fmap g . h) f == (h' . fmap g) f
>
> maybe_to_list :: NatTran Maybe [] a
> maybe_to_list Nothing  = []
> maybe_to_list (Just x) = [x]
>
> test_func :: Num a => a -> (a, a)
> test_func x = (x, x + 1)
>
> success = all (to_assert test_func maybe_to_list maybe_to_list) [Nothing,
> Just 1]
>
> main :: IO ()
> main = do
>     if success then print "Success!" else print "Failure."
>
> main
>
>
> Running this code produces:
>
> "Success!"
>
>
> =================================================
>
> Hi all,
>
> In doing the challenge problems at the end of chapter 10 (*Natural
> Transformations*) in Bartosz Milewski’s “Category Theory for
> Programmers”, I’m trying to write a generic naturality checker:
>
> {-# LANGUAGE Rank2Types
>              AllowAmbiguousTypes
>   #-}
>
> type NatTran a = (Functor f, Functor f') => f a -> f' a
>
> to_assert :: (Functor f, Eq b) => (a -> b) -> NatTran a -> NatTran b -> f
> a -> Bool
> to_assert g h h' f = (fmap g . h) f == (h' . fmap g) f
>
>
> which is later made specific to a particular natural transformation:
>
> maybe_to_list :: Maybe a -> [a]
> maybe_to_list Nothing  = []
> maybe_to_list (Just x) = [x]
>
> test_func :: Num a => a -> (a, a)
> test_func x = (x, x + 1)
>
> assertions = map (to_assert test_func maybe_to_list) [Nothing, Just 1]
>
>
> but I’m getting this from ghc:
>
> Could not deduce (Functor f0) arising from a use of ‘fmap’
> from the context (Functor f, Eq b)
> bound by the type signature for interactive:IHaskell465.to_assert ::
> (Functor f, Eq b) => (a -> b) -> interactive:IHaskell465.NatTran a ->
> interactive:IHaskell465.NatTran b -> f a -> Bool at :2:14-83
> The type variable ‘f0’ is ambiguous
> Note: there are several potential instances:
> instance Monad m => Functor (Data.Vector.Fusion.Bundle.Monadic.Bundle m v)
> -- Defined in ‘Data.Vector.Fusion.Bundle.Monadic’
> instance Functor Data.Vector.Fusion.Util.Box -- Defined in
> ‘Data.Vector.Fusion.Util’
> instance Functor Data.Vector.Fusion.Util.Id -- Defined in
> ‘Data.Vector.Fusion.Util’
> ...plus 27 others
> In the first argument of ‘(.)’, namely ‘fmap g’
> In the expression: fmap g . h
> In the first argument of ‘(==)’, namely ‘(fmap g . h) f’
>
> Can anyone offer some advice?
>
> Thanks,
> -db
>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160618/e36a11dd/attachment.html>


More information about the Haskell-Cafe mailing list