Search code examples
haskellexistential-type

An heterogeneous indexed structure without Existential Types?


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 

Solution

  • 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 ...