[Haskell-cafe] How to abstract away set representation

Tom Ellis tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk
Tue Mar 10 16:22:19 UTC 2015


On Mon, Mar 09, 2015 at 09:30:27PM +0100, martin wrote:
> Am 03/08/2015 um 10:05 PM schrieb Tom Ellis:
> How would I use this? If I have a listProf and I want to perform pCount, must I then choose the pCount from listProf?
> Something like
> 
> 	pCount listProf aProfile
> 
> But then my code knows that I am using a list representation, which is the thing I wanted to avoid.
> 
> I tried to pair the ops with the representation, but this also got me into trouble, because when I e.g. do a pAdd then
> it gets strange when the two operands do not use the same Ops.

You use it like this.  You can write operations on your Prof without having
to know its concrete type.  If you don't like threading the dictionary `p`
around then you could use a reader monad or a typeclass.


{-# LANGUAGE Rank2Types #-}

type Count = Int

data ProfOps prof = P {
  pCount  :: forall a. prof a -> Count,
  pFilter :: forall a. (a -> Bool) -> prof a -> prof a,
  pAdd    :: forall a. prof a -> prof a -> prof a
  }
 

listProf :: ProfOps []
listProf = P {
  pCount  = length,
  pFilter = filter,
  pAdd    = (++)
  }

example :: ProfOps prof -> prof Integer -> prof Integer -> Count
example p profs1 profs2 = pCount p (pAdd p (pFilter p even profs1) profs2)



Tom


More information about the Haskell-Cafe mailing list