[Haskell-cafe] Re: Polyvariadic functions operating with a monoid

Kevin Jardine kevinjardine at gmail.com
Sun Oct 10 16:31:29 EDT 2010


One final example to end with:

-- mixed type product example

instance Monoid Double where
    mappend = (*)
    mempty = (1.0) :: Double

instance Monoidable Int Double where
    toMonoid = fromIntegral

instance Monoidable Double Double where
    toMonoid = id

#define productOf(VALUES) poly(Double,VALUES)

testProduct = putStrLn $ show $ productOf ( (5 :: Int) (2.3 :: Double)
(3 :: Int) (8 :: Int) )

If anyone has a better alternative to the CPP macros, I'd be
interested to hear it.

I think that this is interesting enough to create a
PolyvariadicFromMonoid library as it seems to be a fast way to create
a large number of polyvariadic functions - basicially, just set up
your Monoid definition and your toMonoid conversion functions and then
you get the appropriate polvariadic function for free.

Thanks for the input from everyone and Oleg especially for creating
working code!

Kevin

On Oct 10, 2:51 pm, Kevin Jardine <kevinjard... at gmail.com> wrote:
> For example, the notation can be reduced to:
>
> poly([String],True () (Just (5::Int)))
>
> using:
>
> #define poly(TYPE,VALUES) ((polyToMonoid (mempty :: TYPE) VALUES) ::
> TYPE)
>
> which I think is as concise as it can get.
>
> Kevin
>
> On Oct 10, 1:47 pm, Kevin Jardine <kevinjard... at gmail.com> wrote:
>
> > It is interesting to see that the dummy parameters can actually be
> > replaced by:
>
> > mempty :: [String]
> > mempty :: String
> > mempty: Int
>
> > in my three examples and the code still compiles and gives the
> > expected results.
>
> > This suggests that a further simplification might be possible (ideally
> > in straight Haskell, but if not then with CPP or Template Haskell).
>
> > Kevin
>
> > On Oct 10, 1:28 pm, Kevin Jardine <kevinjard... at gmail.com> wrote:
>
> > > For anyone who's interested, the code I have now is:
>
> > > {-# LANGUAGE TypeSynonymInstances, FlexibleInstances,
> > > MultiParamTypeClasses #-}
> > > module PolyTest where
>
> > > import Data.Monoid
>
> > > class Monoid m => Monoidable a m where
> > >     toMonoid :: a -> m
>
> > > squish :: Monoidable a m => m -> a -> m
> > > squish m a = (m `mappend` (toMonoid a))
>
> > > class Monoid m => PolyVariadic m r where
> > >     polyToMonoid :: m -> r
>
> > > instance Monoid m => PolyVariadic m m where
> > >     polyToMonoid acc = acc
>
> > > instance (Monoidable a m, PolyVariadic m r) => PolyVariadic m (a->r)
> > > where
> > >     polyToMonoid acc = \a -> polyToMonoid (squish acc a)
>
> > > and three example uses are:
>
> > > -- [String] example
> > > instance Show a => Monoidable a [String] where
> > >     toMonoid a = [show a]
>
> > > testStringList = putStrLn $ show $ ((polyToMonoid [""] True () (Just
> > > (5::Int))) :: [String])
>
> > > -- String example
> > > instance Show a => Monoidable a String where
> > >     toMonoid a = show a
>
> > > testString = putStrLn $ ((polyToMonoid "" True () (Just (5::Int))) ::
> > > String)
>
> > > -- sum example
>
> > > instance Monoid Int where
> > >     mappend = (+)
> > >     mempty = 0
>
> > > instance Monoidable Int Int where
> > >     toMonoid = id
>
> > > testSum = putStrLn $ show $ ((polyToMonoid (0::Int) (1::Int) (2::Int)
> > > (3::Int)) :: Int)
>
> > > main = do
> > >     testStringList
> > >     testString
> > >     testSum
>
> > > $ runhaskell PolyTest.hs
> > > ["","True","()","Just 5"]
> > > True()Just 5
> > > 6
>
> > > This removes the unwrap and I don't mind the need for the outer type
> > > cast.
>
> > > I do wonder if there is a need for the first (dummy) parameter to
> > > communicate the type as well as this seems redundant given the outer
> > > type cast but I can't find a way to remove it.
>
> > > It appears that GHC needs to be told the type both coming and going so
> > > to speak for this to work consistently.
>
> > > Any suggestions for improvement welcome!
>
> > > Kevin
>
> > > On Oct 10, 11:12 am, Kevin Jardine <kevinjard... at gmail.com> wrote:
>
> > > > OK, upon further investigation, the problem is that GHC cannot in
> > > > general infer the return type of polyToMonoid despite the hint it is
> > > > given (the type signature of the first parameter).
>
> > > > If I write:
>
> > > > main = putStrLn $ show $ unwrap $ ((polyToMonoid [""] True (Just
> > > > (5::Int))) :: WMonoid [String])
>
> > > > or
>
> > > > main = putStrLn $ show $ unwrap $ ((polyToMonoid (0::Int) (1::Int)
> > > > (2::Int) (3::Int)) :: WMonoid Int)
>
> > > > the code compiles and returns the expected result.
>
> > > > Kevin
>
> > > > On Oct 10, 8:58 am, Kevin Jardine <kevinjard... at gmail.com> wrote:
>
> > > > > And in fact in both cases, it appears that GHC is trying to derive the
> > > > > *wrong* instances of PolyVariadic.
>
> > > > > It should be deriving:
>
> > > > > PolyVariadic Int (WMonoid Int)
>
> > > > > not
>
> > > > > PolyVariadic Int (WMonoid m)
>
> > > > > and
>
> > > > > PolyVariadic [String] (WMonoid [String])
>
> > > > > not
>
> > > > > PolyVariadic [String] (WMonoid String)
>
> > > > > specifically, GHC is attempting to derive PolyVariadic with the wrong
> > > > > version of WMonoid in each case.
>
> > > > > I'm using GHC 6.12.3
>
> > > > > Perhaps the new GHC 7 type system would work better?
>
> > > > > Kevin
>
> > > > > On Oct 10, 8:26 am, Kevin Jardine <kevinjard... at gmail.com> wrote:
>
> > > > > > Hi Brandon,
>
> > > > > > True, when I replace [] with [""], I get a different error message:
>
> > > > > >  No instance for (PolyVariadic [[Char]] (WMonoid String))
>
> > > > > > which now looks a bit like the Int example. In both cases, GHC appears
> > > > > > to be unable to derive the appropriate instance of PolyVariadic. Why
> > > > > > this is so, but worked for Oleg's specific example. is still not clear
> > > > > > to me.
>
> > > > > > Kevin
>
> > > > > > On Oct 9, 11:51 pm, Brandon S Allbery KF8NH <allb... at ece.cmu.edu>
> > > > > > wrote:
>
> > > > > > > -----BEGIN PGP SIGNED MESSAGE-----
> > > > > > > Hash: SHA1
>
> > > > > > > On 10/9/10 10:25 , Kevin Jardine wrote:
>
> > > > > > > > instance Show a => Monoidable a [String] where
> > > > > > > >     toMonoid a = [show a]
>
> > > > > > > > main = putStrLn $ unwrap $ polyToMonoid [] True () (Just (5::Int))
>
> > > > > > > > fails to compile.
>
> > > > > > > > Why would that be? My understanding is that all lists are
> > > > > > > > automatically monoids.
>
> > > > > > > I *think* the problem here is that Oleg specifically pointed out that the
> > > > > > > first parameter to polyToMonoid must specify the type of the monoid.  []
> > > > > > > tells you it's a list, therefore a monoid, but it doesn't say enough to
> > > > > > > allow the [String] instance to be chosen.  (No, the fact that you only
> > > > > > > declared an instance for [String] isn't really enough.)
>
> > > > > > > - --
> > > > > > > brandon s. allbery     [linux,solaris,freebsd,perl]      allb... at kf8nh.com
> > > > > > > system administrator  [openafs,heimdal,too many hats]  allb... at ece.cmu.edu
> > > > > > > electrical and computer engineering, carnegie mellon university      KF8NH
> > > > > > > -----BEGIN PGP SIGNATURE-----
> > > > > > > Version: GnuPG v2.0.10 (Darwin)
> > > > > > > Comment: Using GnuPG with Mozilla -http://enigmail.mozdev.org/
>
> > > > > > > iEYEARECAAYFAkyw49wACgkQIn7hlCsL25VZygCfVETk+3AZ3gKoBy4pZ7j8g4Km
> > > > > > > WXgAnjrbO9rEl2HnQtGQ31EyRuhWzI4r
> > > > > > > =YMDw
> > > > > > > -----END PGP SIGNATURE-----
> > > > > > > _______________________________________________
> > > > > > > Haskell-Cafe mailing list
> > > > > > > Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
>
> > > > > > _______________________________________________
> > > > > > Haskell-Cafe mailing list
> > > > > > Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
>
> > > > > _______________________________________________
> > > > > Haskell-Cafe mailing list
> > > > > Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
>
> > > > _______________________________________________
> > > > Haskell-Cafe mailing list
> > > > Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
>
> > > _______________________________________________
> > > Haskell-Cafe mailing list
> > > Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
>
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list