Search code examples
haskelltypesfunctional-programmingfunctional-dependenciesassociated-types

How can we handle associated types generically while keeping type-safety


Here is my problem :

Let's say I have various kinds of objects to handle but they share the same form : We have Items that are made of a String (say an id) and of a Content which can be anything. So the broken-down problem can be summarized as follow : I'd like to be able to produce an item from a content associating it an id in a generic manner but I'd like the type-system to constrain the interface such that I know I'll get back the an Item of the passed content.

Here is an example of an attempt using FunctionalDependencies :

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}

main :: IO ()
main = do
  putStrLn $ show $ handleContent TitiAssociation $ read "TitiContent"
  putStrLn $ show $ handleContent TotoAssociation $ read "TotoContent"
-- Expected
-- "TitiItem"
-- "TotoItem"

-- definition of the domain
data TitiContent = TitiContent String deriving (Read, Show)
data TotoContent = TotoContent String deriving (Read, Show)

data TitiItem = TitiItem String TitiContent deriving (Read, Show)
data TotoItem = TotoItem String TotoContent deriving (Read, Show)

--
class (Read a, Show a) => Content a where
class (Read a, Show a) => Item a where

instance Content TitiContent where
instance Content TotoContent where

instance Item TitiItem where
instance Item TotoItem where

-- Association of types
class (Content contentType, Item itemType) => ItemContentAssociation association contentType itemType | association -> contentType, association -> itemType, itemType -> association where

-- tokens to identify the types which will be handled
data TitiAssociation = TitiAssociation
data TotoAssociation = TotoAssociation

instance ItemContentAssociation TitiAssociation TitiContent TitiItem where
instance ItemContentAssociation TotoAssociation TotoContent TotoItem where

-- generic function for handling
handleContent :: (ItemContentAssociation association contentType itemType) => association -> contentType -> itemType
handleContent TitiAssociation TitiContent = TitiItem
handleContent TotoAssociation TotoContent = TotoItem

but then the compiler complains :

tmp.hs:41:15: error:
    * Couldn't match expected type `ass' with actual type `TitiAss'
      `ass' is a rigid type variable bound by
        the type signature for:
          handleContent :: forall ass contentType itemType.
                           ItemContentAss ass contentType itemType =>
                           ass -> contentType -> itemType
        at tmp.hs:40:1-92
    * In the pattern: TitiAss
      In an equation for `handleContent':
          handleContent TitiAss TitiContent = TitiItem
    * Relevant bindings include
        handleContent :: ass -> contentType -> itemType
          (bound at tmp.hs:41:1)

I've also tried various flavours of the TypeFamilies extension but the compiler always complains (could provide more example if required but intended to keep the initial post of a reasonable size at first).

I'm quite new in the world of functionanl programming so do not hesitate to bring up new approaches as I'm sure I'm overlooking many aspects of the problem.

Thanks a lot in advance, Cheers !


Solution

  • Almost certainly the right answer, in both the MPTCs/FunDeps world and in the TF world, is to make handleContent a method of ItemContentAssociation. Here's specifically what that would look like with type families, since you ask about that in the comments.

    {-# LANGUAGE FlexibleContexts #-}
    {-# LANGUAGE TypeFamilies #-}
    {-# LANGUAGE TypeFamilyDependencies #-}
    
    main :: IO ()
    main = do
      putStrLn $ show $ handleContent TitiAssociation $ read "TitiContent \"titi\""
      putStrLn $ show $ handleContent TotoAssociation $ read "TotoContent \"toto\""
    -- Expected
    -- "TitiItem"
    -- "TotoItem"
    
    -- definition of the domain
    data TitiContent = TitiContent String deriving (Read, Show)
    data TotoContent = TotoContent String deriving (Read, Show)
    
    data TitiItem = TitiItem String TitiContent deriving (Read, Show)
    data TotoItem = TotoItem String TotoContent deriving (Read, Show)
    
    --
    class (Read a, Show a) => Content a where
    class (Read a, Show a) => Item a where
    
    instance Content TitiContent where
    instance Content TotoContent where
    
    instance Item TitiItem where
    instance Item TotoItem where
    
    -- Association of types
    class (Content (ContentType association), Item (ItemType association)) =>
        ItemContentAssociation association
        where
        type ContentType association = content | content -> association
        type ItemType association
        handleContent :: association -> ContentType association -> ItemType association
    
    -- tokens to identify the types which will be handled
    data TitiAssociation = TitiAssociation
    data TotoAssociation = TotoAssociation
    
    instance ItemContentAssociation TitiAssociation where
        type ContentType TitiAssociation = TitiContent
        type ItemType TitiAssociation = TitiItem
        handleContent TitiAssociation c@(TitiContent s) = TitiItem s {- what string should be used here? if s, why also have c? -} c
    
    instance ItemContentAssociation TotoAssociation where
        type ContentType TotoAssociation = TotoContent
        type ItemType TotoAssociation = TotoItem
        handleContent TotoAssociation c@(TotoContent s) = TotoItem s {- what string? -} c
    

    That said, something smells very wrong here. The amount of duplicated code makes me suspect you're bringing a wrong idea about how to set things up from your other favorite language(s). It's hard to say more about how to fix it without learning more about what motivated these definitions, though.