ryachza
ryachza

Reputation: 4540

Is it possible to represent this transformation in a strongly typed manner?

I'm looking to perform a transformation like (in F#):

type Test = TBool of bool | TString of string

type TestList = TLBool of bool list | TLString of string list

let transform : Map<int, Test> list -> Map<int, TestList> = ??

Is there a way to encode this such that we "know" that while the Map contains heterogeneous values, the value at each position is the same type across elements of the containing list? The Maps would be of static size once constructed and the same across each list element, but the size is not known in advance so I'm basically looking to generate tuples/records of an unknown size.

Edit

I think my example was unclear. The root of what I'm after is to be able to take two variable sized collections whose values at a given position are always the same type, but that the collection itself can contain values of multiple types, and "zip" them together using the knowledge that at a given position the two values are the same type. Specifically, I don't want to have to recheck that they are the same and propagate the condition that they vary (as an error of some sort), since I already do exactly that when initially creating the collections.

Edit 2

From a comment posted below: I do essentially want heterogenous lists (I used maps since my indices can be sparse, but I could always use lists with an index mapping), but with the additional constraint that two instances of the heterogenous list can be "zipped together" and the values at a given index are of the same type.

Upvotes: 2

Views: 224

Answers (4)

effectfully
effectfully

Reputation: 12715

Heterogeneous lists with elements wrapped in some f are:

{-# LANGUAGE GADTs, DataKinds, TypeOperators #-}

infixr 5 :::

data HList f as where
    HNil  :: HList f '[]
    (:::) :: f a -> HList f as -> HList f (a ': as)

For example,

xs1 :: HList [] [Bool, Int]
xs1 = [True, False] ::: [1..3] ::: HNil

xs2 :: HList [] [Bool, Int]
xs2 = [True]        ::: [1..5] ::: HNil

It's easy to zip two HList []:

hzip :: HList [] as -> HList [] as -> HList [] as
hzip  HNil         HNil        = HNil
hzip (xs ::: xss) (ys ::: yss) = (xs ++ ys) ::: hzip xss yss

Or a bit more generally (and with the Rank2Types extension):

hzipWith :: (forall a. f a -> g a -> h a) -> HList f as -> HList g as -> HList h as
hzipWith f  HNil       HNil      = HNil
hzipWith f (x ::: xs) (y ::: ys) = f x y ::: hzipWith f xs ys

hzip :: HList [] as -> HList [] as -> HList [] as
hzip = hzipWith (++)

Then (requires FlexibleInstances and FlexibleContexts)

instance Show (HList f '[]) where
    show HNil = "HNil"

instance (Show (f a), Show (HList f as)) => Show (HList f (a ': as)) where
    show (x ::: xs) = show x ++ " ::: " ++ show xs 

main = print $ hzip xs1 xs2

prints [True,False,True] ::: [1,2,3,1,2,3,4,5] ::: HNil.

Upvotes: 0

Daniel
Daniel

Reputation: 47904

If you can do with Test list instead of TestList, the conversion is fairly straightforward:

let transform listOfMaps : Map<int, Test list> =
    listOfMaps
    |> Seq.collect Map.toSeq 
    |> Seq.groupBy fst
    |> Seq.map (fun (i, s) -> 
        let xs = s |> Seq.map snd |> Seq.toList
        i, xs)
    |> Map.ofSeq

As far as capturing your assumptions in the types, I suspect it's either impossible or much more effort than it's worth.

Upvotes: 0

Luis Casillas
Luis Casillas

Reputation: 30237

Edit [...] The root of what I'm after is to be able to take two variable sized collections whose values at a given position are always the same type, but that the collection itself can contain values of multiple types, and "zip" them together using the knowledge that at a given position the two values are the same type.

This, in its broadest reading, fundamentally requires that the types of the collections encode which position contains which element type, and this dips into dependent types territory.

If there is one fixed shape of collection that can be determined at compilation time, however, then it's easy—you just write a type all of whose values have that shape.

Upvotes: 1

Tomas Petricek
Tomas Petricek

Reputation: 243061

You could define a transformMap function that has the property you want (i.e. preserves the key and turns strings to lists of strings and bools to lists of bools). The function can still be fully parametric in what it does with the values:

let transformMap fstr fbool map = 
  map |> Map.map (fun k v -> 
    match v with 
    | TBool b -> TLBool(fbool k b)
    | TString s -> TLString(fstr k s) )

Any transformation that you then perform on your map using transformMap has the properties you want. If you wanted to be more strict, you could write a wrapper over Map<'K, TestList> and hide the internal representation, which would give you a strong guarantee. In practice, I think it is probably reasonable to make the internals public, but check by hand that you only manipulate the map using your correct transformation function.

An example that turns each value into a singleton list using this function looks like this:

Map.empty |> transformMap
  (fun k s -> [s])
  (fun k b -> [b])

Upvotes: 0

Related Questions