12

I want to make a special smart constructor for Data.Map with a certain constraint on the types of key/value pair relationships. This is the constraint I tried to express:

{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, DataKinds #-}

data Field = Speed | Name | ID
data Value = VFloat Float | VString ByteString | VInt Int

class Pair f b | f -> b where
    toPair :: f -> b -> (f, b)
    toPair = (,)

instance Pair Speed (VFloat f) 
instance Pair ID (VInt i)

for each field, there is only one type of value that it should be associated with. In my case, it does not make sense for a Speed field to map to a ByteString. A Speed field should uniquely map to a Float

But I get the following type error:

Kind mis-match
The first argument of `Pair' should have kind `*',
but `VInt' has kind `Value'
In the instance declaration for `Pair Speed (VFloat f)'

using -XKindSignatures:

class Pair (f :: Field) (b :: Value) | f -> b where
    toPair :: f -> b -> (f, b)
    toPair = (,)

Kind mis-match
Expected kind `OpenKind', but `f' has kind `Field'
In the type `f -> b -> (f, b)'
In the class declaration for `Pair'

I understand why I get the Kind mis-match, but how can I express this constraint so that it is a compile time type-checker error to use toPair on an non-matching Field and Value.

It was suggested to me by #haskell to use a GADT, but I havent been able to figure it out yet.

The goal of this is to be able to write

type Record = Map Field Value

mkRecord :: [Field] -> [Value] -> Record
mkRecord = (fromList .) . zipWith toPair

so that I can make safe Maps where the key/value invariants are respected.

So this should type-check

test1 = mkRecord [Speed, ID] [VFloat 1.0, VInt 2]

but this should be a compile time error

test2 = mkRecord [Speed] [VInt 1]

EDIT:

I'm beginning to think that my specific requirements aren't possible. Using my original example

data Foo = FooInt | FooFloat
data Bar = BarInt Int | BarFloat Float

In order to enforce the constraint on Foo and Bar, there must be some way to differentiate between a FooInt and FooFloat at the type level and similarly for Bar. Thus I instead need two GADTs

data Foo :: * -> * where
    FooInt   :: Foo Int
    FooFloat :: Foo Float

data Bar :: * -> * where
    BarInt   :: Int   -> Bar Int
    BarFloat :: Float -> Bar Float

now I can write an instance for Pair that only holds when the Foo and Bar are both tagged with the same type

instance Pair (Foo a) (Bar a)

and I have the properties I want

test1 = toPair FooInt (BarInt 1)   -- type-checks
test2 = toPair FooInt (BarFloat 1) -- no instance for Pair (Foo Int) (Bar Float)

but I lose the ability to write xs = [FooInt, FooFloat] because that would require a heterogeneous list. Furthermore if I try to make the Map synonym type FooBar = Map (Foo ?) (Bar ?) I'm stuck with a Map of either only Int types or only Float types, which isnt what I want. It's looking rather hopeless, unless theres some powerful type class wizardry I'm not aware of.

cdk
  • 6,698
  • 24
  • 51
  • Have you tried [explicit kind signatures](http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/other-type-extensions.html#kinding)? Just curious. – n. m. could be an AI Feb 28 '13 at 03:54
  • 2
    Why not use a data family. Then the type of the Map can be tied to the type of key. – MFlamer Feb 28 '13 at 04:33
  • These questions of mine are similar and might help. http://stackoverflow.com/questions/14949021/return-type-as-a-result-of-term-or-value-calculation http://stackoverflow.com/questions/14918867/trouble-with-datakinds – MFlamer Feb 28 '13 at 21:57
  • a simpleton question: if the correspondence is one to one, why not use just one simple data definition `data Field = Speed Float | Name ByteString | ID Int`? you could just write `test1 = [Speed 1.0, ID 2]`, but `test2=[Speed (1::Int)]` would give a compile time error. What do you want to do that would be impossible this way? Do you really need to have uninstantiated fields? – Will Ness Mar 01 '13 at 11:21
  • @WillNess: I need to be able to lookup the `Value` related to the `Field`, and it needs to be similar to `Map` because I do need uninstantiated `Field`s. If the `Field` contains all the information, it defeats the point of lookups because I'll have to already know the value the `Field` contains. – cdk Mar 01 '13 at 15:01
  • if you only have three types of field, why not have three string keys, or three ints even (1,2, and 3) i.e. some enumeration, to represent an uninstantiated field. then you can have a constructor function `mkField 1 speed = Speed Val; mkField 2 name = Name name; mkField 3 id = ID id` to construct full values. .... I see, the types... – Will Ness Mar 01 '13 at 15:03
  • @WillNess: this is a simplified example. I actually have ~30 fields, thats why I'm looking for an elegant solution to make this easier to work with. – cdk Mar 01 '13 at 15:07
  • I see. You could push `Maybe` into the fields, `data Field = Speed (Maybe Float) | ...` and have `Nothing` to represent the uninstantiated values. – Will Ness Mar 01 '13 at 15:09
  • Thats the problem I was trying to solve with a `Map`. I want to avoid having a record structure with ~30 entries, all `Maybe Field`. With a `Map` I only have to worry about the entries that I actually use, and let the lookup semantics worry about if the entry actually exists or not. – cdk Mar 01 '13 at 15:11
  • let us [continue this discussion in chat](http://chat.stackoverflow.com/rooms/25367/discussion-between-will-ness-and-chris-dueck) – Will Ness Mar 01 '13 at 15:25

4 Answers4

5

You could use a GADT like so,

data Bar :: * -> * where
   BarInt   :: Int -> Bar Int
   BarFloat :: Float -> Bar Float

now you have 2 distinct types of Bar available (Bar Int) and (Bar Float).You could then just split Foo into 2 types unless there is a reason not to.

data FooInt 
data FooFloat

class Pair f b c| f b -> c where
    toPair :: f -> b -> c

instance Pair FooInt (Bar Int) (FooInt,Int) where
    toPair a (BarInt b)= (a,b) 

This is sort of a clumsy example but it shows how you can specialize the type using a GADT. The idea is that they carry a "phantom type" along. It is described pretty well on this page and with DataKinds on this page.

EDIT:

If we make both Foo and Bar GADT's we can use a type or data family as described here. So, this combination allows us to set the type of Map based on the key type. Still feels like there are other possibly simpler ways to accomplish this, but it does showcase 2 great GHC extensions!

data Foo :: * -> * where
   FooInt   :: Int   -> Foo Int
   FooFloat :: Float -> Foo Float

data Bar :: * -> * where
   BarInt   :: Int   -> Bar Int
   BarFloat :: Float -> Bar Float

class Pair f b c| f b -> c where
    toPair :: f -> b -> c

instance Pair (Foo Int) (Bar Int) ((Foo Int),Int) where
   toPair a (BarInt b)= (a,b)    


type family FooMap k :: *

type instance FooMap (Foo Int) = Map (Foo Int) (Bar Int)
MFlamer
  • 2,340
  • 2
  • 18
  • 25
  • this is really close to what I need. Is there any way to do it without splitting Foo into 2 types? I need there to be one unified Foo type. – cdk Feb 28 '13 at 13:07
  • Actually, I'm not sure this works. As well as needing a unified Foo type, I dont think I can write `type FooBar = Map Foo Bar` since Bar doesnt have kind * – cdk Feb 28 '13 at 14:31
  • I think we can make this work nicely for you, give me a bit and I'll try to come up with something – MFlamer Feb 28 '13 at 17:02
  • Can you explain a little more about your types? It might help produce a better solution. – MFlamer Feb 28 '13 at 17:38
  • Is Foo really going to be the Map key? – MFlamer Feb 28 '13 at 17:47
  • Foo is really some C/Java style enum type for fields of a message data type that I'm trying to work with. Each field will be associated with a value in the map, but given the type of the field I already know the unique type of value that is allowed. If the field is "Speed" for example, in my case I know that the only allowed value should be a Float. But if the field is "Name", then the only allowed value should be ByteString. I want to be able to write a safe constructor for Map so that these invariants hold and are type-checked at compile time. – cdk Feb 28 '13 at 17:49
  • This seems like a possible step in the right direction, but doesnt really satisfy any of the requirements of my question. Namely, I can't write `[BarInt 1, BarFloat 2]` because their types are `Bar Int` and `Bar Float` respectively and a list must be homogeneous. I need my map to contain keys with type constructors `FooInt` AND `FooFloat` as well as the correct values with type constructors `BarInt` AND `BarFloat`. I'm starting to think this might not be possible... – cdk Feb 28 '13 at 20:15
4

An oldschool version using Dynamic and Typeable and FunDeps. To keep it safe, you just need to not export the abstraction-breaking things like the SM constructor and the SMKey typeclass.

{-# LANGUAGE DeriveDataTypeable, MultiParamTypeClasses, FunctionalDependencies, TypeSynonymInstances, FlexibleInstances #-}
module Main where
import qualified Data.Map as M
import Data.Dynamic
import Data.Typeable

data SpecialMap = SM (M.Map String Dynamic)

emptySM = SM (M.empty)

class (Typeable a, Typeable b) => SMKey a b | a -> b

data Speed = Speed deriving Typeable
data Name = Name deriving Typeable
data ID = ID deriving Typeable

instance SMKey Speed Float
instance SMKey Name String
instance SMKey ID Int

insertSM :: SMKey k v => k -> v -> SpecialMap -> SpecialMap
insertSM k v (SM m) = SM (M.insert (show $ typeOf k) (toDyn v) m)

lookupSM :: SMKey k v => k -> SpecialMap -> Maybe v
lookupSM k (SM m) =  fromDynamic =<< M.lookup (show $ typeOf k) m

-- and now lists

newtype SMPair = SMPair {unSMPair :: (String, Dynamic)}
toSMPair :: SMKey k v => k -> v -> SMPair
toSMPair k v = SMPair (show $ typeOf k, toDyn v)

fromPairList :: [SMPair] -> SpecialMap
fromPairList = SM . M.fromList . map unSMPair

{-
*Main> let x = fromPairList [toSMPair Speed 1.2, toSMPair ID 34]
*Main> lookupSM Speed x
Just 1.2
-}
sclv
  • 38,665
  • 7
  • 99
  • 204
  • this answer came closest to what I need. If it was possible to keep `Speed` `Name` and `ID` under one type it would be exactly correct. – cdk Mar 09 '13 at 18:19
  • With data kinds you can sort of fake that here. They'll still be different types _as well_, but they'll also be declared as uniform values at the value level. I don't have 7.6 on my box, so I didn't go there :-) – sclv Mar 09 '13 at 22:27
  • Also I don't think that adds anything useful to this solution, or even cuts down on code, all told :-( – sclv Mar 09 '13 at 22:27
2

When I first read this I attempted to solve the problem of forcing compile errors in the required cases, but something seemed wrong. I then tried an approach with multiple maps and a lifting function, but something was still nagging me. However, when I realised that essentially what you are trying to do is create some form of extensible record, it reminded me of a very cool package I had become aware of a few months ago: the Vinyl package (available on Hackage). This may or may not be exactly the effects you were after, and it does require GHC 7.6, but here is an example adapted from the readme:

{-# LANGUAGE DataKinds, TypeOperators #-}
{-# LANGUAGE FlexibleContexts, NoMonomorphismRestriction #-}

import Data.Vinyl

speed = Field :: "speed" ::: Float
name  = Field :: "name"  ::: String
iD    = Field :: "id"    ::: Int

Now a record can be made containing any number of these fields:

test1 = speed =: 0.2

test2 = speed =: 0.2 
    <+> name  =: "Ted"
    <+> iD    =: 1

These are of different types, so an attempt to pass the wrong amount of information in a given function will cause a compile error. A type synonym can make this easier to use, but type annotations are not required.

type Entity = Rec ["speed" ::: Float, "name" ::: String, "id" ::: Int]
test2 :: Entity

The library provides automatic lenses on these types without the need for Template Haskell, and a casting function that allows for subtypes to be handled with ease. For example:

test2Casted :: Rec '["speed" ::: Float]
test2Casted = cast test2

(The extra tick is required to get the kind right for the single field record).

This doesn't allow the exact type for mkRecord you were after, but it does seem to capture the requirements of static checking of extensible records. If this doesn't work for you, you might nevertheless be able to use of the clever type techniques found in the Vinyl source to get where you want to go.

Vic Smith
  • 3,477
  • 1
  • 18
  • 29
-1

I would make an opaque datatype with some getters and setters.

module Rec (Rec, getSpeed, getName, getID, setSpeed, setName, setID, blank) where

data Rec = R { speed :: Maybe Double; name :: Maybe String; id :: Maybe Int }

getSpeed :: Rec -> Maybe Double
getSpeed = speed

setSpeed :: Double -> Rec -> Rec
setSpeed s r = r { speed = s }

blank = R { speed = Nothing, name = Nothing, id = Nothing }
NovaDenizen
  • 5,089
  • 14
  • 28