13

I have a collection of records spread across a number of types in a large Haskell application that reference each other. All of the types involved implement a common typeclass. The typeclass contains functions that work over a variable and all of its children, very much like uniplate's para function.

This is a simplified code sample of what I'd like to build. Is it possible (and reasonable) to get generic functionality to fold over record fields that implement a given typeclass in GHC...

{-# LANGUAGE RankNTypes #-}

myPara :: forall a r . (Data a, Foo a)
       => (forall b . Foo b => b -> [r] -> r)
       -> a
       -> r

-- or as a fold
myFold :: forall a r . (Data a, Foo a)
       => (forall b . Foo b => r -> b -> r)
       -> r
       -> b
       -> r

But generic enough to work with an arbitrary typeclass?

{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE DeriveDataTypeable #-}

import Data.Data
import Data.Generics.Uniplate.Data

class Foo a where 
  fooConst :: a -> Int

data Bar = Bar {barBaz :: Baz} deriving (Typeable, Data)

instance Foo Bar where
  fooConst _ = 2

data Baz = Baz {barBar :: Bar} deriving (Typeable, Data)

instance Foo Baz where
  fooConst _ = 3

func :: Int
func = foldl (\ x y -> x + fooConst y) 0 instances where
  instances :: forall a . (Data a, Foo a) => [a]
  instances = universeBi bar
  bar = Bar{barBaz = baz}
  baz = Baz{barBar = bar}

Compiling this with GHC 7.2.1 (obviously) fails:

Repro.hs:21:42:
    Ambiguous type variable `a0' in the constraints:
      (Data a0) arising from a use of `instances' at Repro.hs:21:42-50
      (Foo a0) arising from a use of `instances' at Repro.hs:21:42-50
    Probable fix: add a type signature that fixes these type variable(s)
    In the third argument of `foldl', namely `instances'
    In the expression: foldl (\ x y -> x + fooConst y) 0 instances
    In an equation for `func':
        func
          = foldl (\ x y -> x + fooConst y) 0 instances
          where
              instances :: forall a. (Data a, Foo a) => [a]
              instances = universeBi bar
              bar = Bar {barBaz = baz}
              baz = Baz {barBar = bar}
8
  • By my reading of the uniplate documentation, the type of instances ought to be just [Baz], no? Commented Oct 13, 2011 at 20:57
  • Yes, it's more a theoretical question than anything. Commented Oct 13, 2011 at 21:52
  • I'm not sure I understand what the theoretical question is. Could you make that a bit more precise in your text? (When you ask, "Is it possible to get generic functionality like this?", what does "like this" mean?) Commented Oct 13, 2011 at 21:57
  • 7
    You are beginning to abstract over typeclasses, which Haskell is pretty bad at. Make the class concrete: eg. for Eq, use data Eq a = Eq { eq :: a -> a -> Bool }, then pass it as a parameter. Typeclasses are mainly for notational convenience, let functions do the heavy lifting. Commented Oct 13, 2011 at 23:52
  • 2
    Looks like it might be possible with ConstraintKinds in GHC 7.4 Commented Oct 14, 2011 at 16:17

2 Answers 2

1

You've hit the Existential Antipattern. You shouldn't be using typeclasses for anything except cases when you need compiler to guess the type for you. List of values of type x will stay the list of values of type x no matter what typeclasses you will implement, and you can't break the type system here.

You can:

  1. Use an ad-hoc box type as suggested above. This is just plain ugly.

  2. Implement generic interfaces with message-passing.

    data Foo = Foo { fooConst :: Int }

    bar = Foo 2

    baz = Foo 3

Sign up to request clarification or add additional context in comments.

1 Comment

Link no longer works but is archived: web.archive.org/web/20210616103013/http://…
0

been a while..

Have you tried existentially quantified data constructors?

data Foo = forall a. MyTypeClass a => Bar [a]

func (Bar l) = map typeClassMember a

now, func will work with anything of type Foo, which hides the inner type.

1 Comment

What I want is a generic function, similar to universeBi (from uniplate) that abstracts over typeclasses instead of types. I have functions like the one you're recommending already, but I have a lot of them and I'm trying to simplify a very large chunk of code.

Your Answer

By clicking “Post Your Answer”, you agree to our terms of service and acknowledge you have read our privacy policy.

Start asking to get answers

Find the answer to your question by asking.

Ask question

Explore related questions

See similar questions with these tags.