sandwood
sandwood

Reputation: 2167

How to make a container of heterogeneous type of the same parameterized type?

I am trying to achieve something like this :

I have a parameterized type, let's call it Variable. This one is a Functor Then I want a Container of Variable ( of any Variable, Variable Int, Variable Double, Variable String, etc)

I want that this container is a Functor too.

I managed to make a parameterized container FooContainer but I would like to deal with heterogenous types.

So I created the Bar algebraic data type and the BarContainer. (as suggested here https://wiki.haskell.org/Heterogenous_collections#Algebraic_datatypes) But I don't understand how to make BarContainer a Functor because its constructor takes no parameter.

import Data.List

data Variable a  =  Variable { 
 varName :: String
 ,value  :: [a] } deriving (Show,Read,Eq)

instance  Functor Variable where
 fmap f (Variable name vals ) = Variable  name (fmap f vals)


data FooContainer a = FooContainer {
 fooname:: String
 , pdata :: [Variable a]
 } deriving (Show,Read,Eq)

instance  Functor FooContainer where
 fmap f (FooContainer n p ) = FooContainer n ( Data.List.map (\x-> fmap f x)  p)

data Bar = BarInt [Int] | BarDouble [Double] | BarString  [String] | BarChar [Char] deriving (Show,Read,Eq)

data BarContainer = BarContainer {
 nameB:: String
 , pdataB :: [Bar]
 } deriving (Show,Read,Eq)




fooC = FooContainer "foo Container" [Variable "v1" [5,6], Variable "v2" [2,6,8]]
fooC_plus2 = fmap (+2) fooC


barC = BarContainer "bar Container" [ BarInt [5,1], BarDouble [3.2,2,6], BarString ["bob", "dupont"]]
--barC_plus2 ? 


main = print $ "Hello, world!" ++ ( show fooC_plus2) ++ (show barC)

Upvotes: 2

Views: 202

Answers (2)

HTNW
HTNW

Reputation: 29193

You want a container that contains a String name, and then a list of Values of varying types. The way you've done it, with Bar, you are limited to only certain types of Variable. If you want a true, unrestricted heterogenous container, you'll need a GADT.

data HMapList (f :: k -> Type) (xs :: [k]) :: Type where
  HMNil :: HMapList f '[]
  HMCons :: f x -> HMapList f xs -> HMapList f (x : xs)

data Container xs = Container {
   containerName :: String
 , containerValues :: HMapList Variable xs
 }

Functor is not possible here. Closely related is the concept of a lens, which you can get. Doing this "properly" requires a bit of boilerplate:

data Elem (x :: k) (xs :: [k]) where -- where do I find x in xs?
  Here :: Elem x (x : xs)
  There :: Elem x xs -> Elem x (y : xs)
data SElem (e :: Elem (x :: k) xs) where
  SHere :: SElem Here
  SThere :: SElem e -> SElem (There e)
-- these are like indices: think 0 = (S)Here, 1 = (S)There (S)Here, 2 = (S)There 1, etc.

type family Replace (xs :: [k]) (e :: Elem x xs) (y :: k) :: [k] where
  Replace (_ : xs) Here y = y : xs
  Replace (x : xs) (There e) y = x : Replace xs e y

hmLens :: forall x y xs (e :: Elem x xs) f g. Functor g => SElem e ->
          -- Lens (f x) (f y) (HMapList f xs) (HMapList f (Replace xs e y))
          (f x -> g (f y)) -> HMapList f xs -> g (HMapList f (Replace xs e y))
hmLens SHere mod (HMCons fx xs) = (\fx' -> HMCons fx' xs) <$> mod fx
hmLens (SThere e) mod (HMCons fx xs) = (\xs' -> HMCons fx xs') <$> hmLens e mod xs

hmLens represents the "fields" of a HMapList. You can use operators from the lens library to manipulate the f x contained in a "slot" of a Container, complete with type-changes. That is, once you select a position within the list with an Elem, you get the Functory ability to replace as with bs by using an a -> b. Though, Container isn't acting as a functor itself; rather, it's generating an infinite family of functors that someone more experienced than me can probably name. To perform your example:

container :: Container [Int, Double, String]
container = Container "container" $ HMCons (Variable "v1" [5,1]) $
                                    HMCons (Variable "v2" [3.2,2,6]) $
                                    HMCons (Variable "v3" ["bob", "dupont"])
                                    HMNil
container' :: Container [Int, Double, String]
container' = let Container name vs = container
              in Container name $ vs & (hmLens SHere).mapped %~ (+2)
              --                       ^ access 1st field    ^ modify w/ function
              --                     ^ flip ($)       ^ peek into Variable
-- a proper Lens (Container xs) (Container ys) (HMapList Variable xs) (HMapList Variable ys)
-- would alleviate the match/rebuild pain.

If you want to extend this to apply (+2) to all of the Variable Ints inside a Container (with the potential to change types, like by using show), then you can adapt part of one of my other answers.

Container is also a proper, lowercase-"f" functor. Let's me define a class of categories:

data ZippingWith (f :: a -> b -> Type) (as :: [a]) (bs :: [b]) where
  ZWNil :: ZippingWith f '[] '[]
  ZWCons :: f a b -> ZippingWith f as bs -> ZippingWith f (a : as) (b : bs)

If f :: k -> k -> Type itself identifies a category, so does ZippingWith f. A ZippingWith f-arrow between xs and ys is a list of f-arrows between the elements of xs and ys, in a "zippy" fashion. HMapList f (and Container, therefore) is a functor from ZippingWith (On f (->)) to (->). It lifts a list of functions into a function on a list.

newtype On (f :: i -> o) (arr :: o -> o -> Type) (a :: i) (b :: i)
  = On { runOn :: arr (f a) (f b) }

hmMap :: (ZippingWith (On f (->))) xs              ys              ->
         (->)                      (HMapList f xs) (HMapList f ys)
hmMap ZWNil HMNil = HMNil
hmMap (ZWCons (On axy) as) (HMCons fx xs) = HMCons (axy fx) (hmMap as xs)
containerMap :: (ZippingWith (On Variable (->))) xs             ys             ->
                (->)                             (Container xs) (Container ys)
containerMap as (Container name vs) = Container name (hmMap as vs)

Should f itself be a Functor (which it is, in this case), you get some lifting action from ZippingWith (->) to ZippingWith (On f (->))

zwManyMap :: Functor f => ZippingWith (->) xs ys -> ZippingWith (On f (->)) xs ys
zwManyMap ZWNil = ZWNil
zwManyMap (ZWCons axy as) = ZWCons (On (fmap axy)) (zwManyMap as)

Which gives us more functorness:

hmMapMap :: Functor f =>
            (ZippingWith (->)) xs              ys              ->
            (->)               (HMapList f xs) (HMapList f ys)
hmMapMap = hmMap . zwManyMap
containerMapMap :: (ZippingWith (->)) xs             ys             ->
                   (->)               (Container xs) (Container ys)
containerMapMap = containerMap . zwManyMap

But wait; there's more: a functor category is a category where objects are functors (f, g) and arrows are natural transformations (f ~> g = forall a. f a -> g a). HMapList is actually a bifunctor. You've seen the ZippingWith (On f (->)) to (->) functor. Now see the (~>) to (->) functor.

hmLMap :: (forall x. f x -> g x) ->
          HMapList f xs -> HMapList g xs
hmLMap _ HMNil = HMNil
hmLMap f (HMCons fx xs) = HMCons (f fx) (hmLMap f xs)

This one doesn't generalize to Container, unless you redefine it:

data Container f xs = Container {
    containerName :: String
  , containerValues :: HMapList f xs
  }

If you do choose to keep your BarContainer representation, containerMap and containerMapMap degrade to some useable remnants. Again, they are more lensy than functory, but they are workable.

-- "type-changing": e.g. BarInt can become BarChar, if desired
containerMapChanging :: ([Int] -> Bar) -> ([Double] -> Bar) ->
                        ([String] -> Bar) -> ([Char] -> Bar) ->
                        BarContainer -> BarContainer
containerMapChanging i d s c (BarContainer name bs) = BarContainer name (f <$> bs)
  where f (BarInt x) = i x
        f (BarDouble x) = d x
        f (BarString x) = s x
        f (BarChar x) = c x

containerMap :: ([Int] -> [Int]) -> ([Double] -> [Double]) ->
                ([String] -> [String]) -> ([Char] -> [Char]) ->
                BarContainer -> BarContainer
containerMap i d s c bc = containerMapChanging (BarInt . i) (BarDouble . d)
                                               (BarString . s) (BarChar . c)
                                               bc

containerMapMap :: (Int -> Int) -> (Double -> Double) ->
                   (String -> String) -> (Char -> Char) ->
                   BarContainer -> BarContainer
containerMapMap i d s c bc = containerMap (map i) (map d) (map s) (map c) bc

So, e.g. if I want to add 2 to every Int in a BarContainer and strip the first character of every String, I can use containerMapMap (+2) id tail id.

Upvotes: 2

chi
chi

Reputation: 116139

(This is more like a comment than an answer, but I need more space.)

Such container seems impossible to achieve as stated, but perhaps you are OK with something similar.

Problem 1: suppose we have an heterogeneous container c containing a mixture of Variable Int and Variable String. Then, consider any f :: Int -> Int (say f = succ).

What would fmap f c be? We can't apply f to all the variables. Would f be applied only to Int ones? This would require some runtime type checking, i.e. we need to add Typeable constraints here and there, but Functor does not allow to add such constraint on fmap.

Problem 2:

To use fmap f c the argument c must have type Container T for some type T. What should the index T be?

Maybe there is no index at all. Maybe the index is a type-level list of the types inside the heterogeneous container. E.g. Container '[Int,Int,String,Int].

In any case, Functor can not work with this.

Perhaps what you want, instead, is a custom function like

notFmap :: (Typeable a, Typeable b) => (a -> b) -> Container -> Container

or

notFmap :: (a -> b) -> Container t -> Container (Replace a b t)

with Replace being a suitable type family that processes the index list t and replaces a with b.

Upvotes: 1

Related Questions