5
votes

I am trying to build an heterogeneous indexed structure and came up with the following solution but I was told not to use existential types.

Can you see a better solution ?

I would like to keep the separation between the definition of the interfaces (the type and class) and the concrete implementation (the dataand instance). Edit following @hammar's comment: in the real application, values are not Shown but simply stored an queried; also myDatais more complex with additional records.

If this can lead to a better solution, the exact requirement is to build a map of maps (the inner maps). Each inner map is homogeneous and in the form of Map String a however each inner map may enforce a different type for its values. You may also think of it as a two level indexed structure. The implementation does not have to use a Data.Map but must be efficient.

{-# LANGUAGE ExistentialQuantification #-}
module Scratch.SO_ExtistentialTypes where

import Data.Map

data HeteroValue = forall a. Show a => HV a 

instance Show HeteroValue where
    show (HV b) = show b

type MyMap = Map String HeteroValue

class MyClass c where 
    getMyMap :: c -> MyMap

data MyData = MyData {
    myMap ::  MyMap
}

instance MyClass MyData where
    getMyMap = myMap

This snippet can be run using ghci

let myMap = fromList [("key1", HV "abc"), ("key2", HV 123)] :: MyMap
let myData = MyData myMap
getMyMap myData 
3
@hammar Show is only there to test this snippet in ghci. In the real app, these values are not showed, simply stored and queried.Bruno Grieder
The real question isn't whether you should be using existential types or other such features, it's whether you should be trying to store heterogenous values like this. Why do you need them to be heterogenous? What do you really want to store in this indexed structure? Static typing is your friend. Static typing saves you from a world of pain. Dynamic typing is not a cool language feature, it's a hack. You can put whatever you like in, but on the flip side, at runtime the world can give you whatever it likes.AndrewC
@AndrewC That is an opinion. My understanding is that when you write 'forall a. Contract a =>` all you are asking the 'world' is that what they 'give you' respects the 'Contract'. This perfectly reflects my intent. Maybe my view of the world is more 'dynamic' ? :)Bruno Grieder
Yes, opinion. If you really mean that, you can have that - see my answer. You still haven't clarified the purpose of your program other than you want to code it in an OO style. What do you want to store? What do you want to do with it when it's stored?AndrewC

3 Answers

6
votes

This is a good pattern for Object Oriented languages, but it's a well-known Haskell antipattern. Read that article. I want you to read that more than anything else I say.

See also this answer, but with the proviso that I think GADTs are more elegant than existential types (see below).


Please try to find the best functional programming ways of writing your program, rather than the best functional programming ways of re-implementing object oriented programming. You still haven't made any purpose of your code clear other than your hope to program in an OO style.

(Imagine Craig, a C programmer new to Java who is trying to find how to make a pointer to an array of structs or getting stuck when trying to make a method with the functionality of malloc, or getting frustrated because there's no pointer arithmetic. Janet the Java programmer would respond by asking Craig why he wanted to do the pointers himself, what was wrong with garbage collection, and why on earth anyone would ever want pointer arithmetic when they had arrays with built-in bounds checks? Really Craig would be better off learning to program idiomatic Java first before deciding which features of C he really can't do without. OO is a different paradigm to C's close-as-possible-to-the-machine-whilst-still-being-relatively-machine-independent philosophy. Craig should learn the new paradigm as the first priority. It might make him a better C programmer. Don't visit France to only speak English, watch CNN and eat McDonalds! There's a sense in which you should be trying to write your code in as functional a way as possible.)


If you really want to have no other information about your data than that it obeys your contract, one way is to use a GADT. You should be aware that Haskell will hold you to your claim; there's no casting to get you out of a thoughtless design decision. (Casting is a way of turning a compile time check into a runtime check, or to put it a different way, a way of turning compile time errors into runtime errors. I don't see that as a good thing.)

{-# LANGUAGE GADTs #-}

class Contract a where
   toString :: a -> String
   fromInts :: Int -> Int -> a
   alter :: a -> a
   -- other functionality

data Encapsulated where
   Encapsulate :: Contract a => a -> Encapsulated

Now once you've encapsulated your data, you can do anything you like with it as if it were an ordinary data type, and recover any of the Contracted functionality like this:

munged :: Encapsulated -> String
munged (Encapsulate a) = toString.alter.alter.alter $ a

If you like then, you can store a whole bunch of Encapsulated data in a map, there's no need to do anything special or reimplement Data.Map for your existential, because, and here's the powerful functional paradigm: Data.Map makes no assumptions about your data whatsoever. It's parametric polymorphism, and works on anything. Anything at all, even functions. The only assumptions it makes are that your keys are sortable (Ord k =>) and your data is homogeneous (and our GADT is homogeneous, despite being made from heterogenous data).


That's one way of doing what you asked for, but if we knew what you wanted it for, we could give you better advice. (Another new question perhaps!) Please really read the article I linked to, and see if you can implement your class as a data type full of functions/results, and your instances as functions to that data type.

4
votes

One way to do "heterogeneous collections" is with Data.Dynamic.

module Scratch.SO_Dyn where

import Data.Dynamic
import Data.Map

type MyMap = Map String Dynamic

class MyClass c where 
    getMyMap :: c -> MyMap

data MyData = MyData {
    myMap ::  MyMap
}

instance MyClass MyData where
    getMyMap = myMap

The data you wish to put into this map must derive Typeable.
Use {-# LANGUAGE DeriveDataTypeable #-} and deriving (Data, Typeable), see also http://www.haskell.org/ghc/docs/7.6.1/html/users_guide/deriving.html#deriving-typeable.

You can then cast your data to the Dynamic type with toDyn, and safely cast it from the Dynamic type with fromDynamic.


Although this is a perfectly valid approach, I and many other Haskellers would highly recommend that you consider making a custom data type rather than resorting to a truly heterogeneous collection. Suppose (in the spirit of Halloween) that you know for a fact that the only sorts of things you will put into this map are Cats, Witches, and Ghouls.

data Cat = ...
data Witch = ...
data Ghoul = ...

By simply tagging each possible option, you can later determine what each thing is.

data HeteroValue
  = DarkOmen Cat
  | Hag Witch
  | Haunting Ghoul

case (Map.lookup "Midnight visitor" theMap) of
  Just (DarkOmen cat) -> hiss cat
  Just (Hag witch) -> cackle witch
  Just (Haunting ghoul) -> spook ghoul
  Nothing -> error ...
0
votes

Appearently the only thing you can do with a HeteroValue is to show it, i.e. convert it to String. With that in mind there is no point in storing the values, you could as well just store the converted string:

type MyMap = Map String String

or

data HeteroData = HD { getShow :: String }
type MyMap = Map String HeteroData

This can easily be adopted to other typeclasses.

If you instead do things like pattern matching on HeteroValue, existential types are a good solution.