Key-Parametrized Lookup Table

Hello list, I am currently thinking that a problem of mine would best be solved if there was a Map-like data structure in which the value returned is parametrized over the lookup type. I wonder is this makes sense and if such a data structure exists or if it could be created while still being well typed. I essentially want to statically define a scope of Key values and dynamically define a list of keys.
-- Scope of possible keys. type Label = String data Key a where KeyStr :: Label -> Key String KeyInt :: Label -> Key Int KeyChoice :: Label -> [a] -> Key a
-- Some key values, to be extended at runtime. strKey "Some String" strKey' "Another String" intKey "Some integer" choiceKey "Chose one" [ "a", "b", "c" ] :: KeyChoice String
Now I need a data structure to possibly associate a value to the key.
data MapG = ... type Value a = a insert :: Key a -> Value a -> MapG Key Value -> MapG Key Value lookup :: Key a -> MapG Key Value -> Maybe (Value a)
I tried implementing this with multiple Map k a's. I tried adding a phantom type on some storage type of to implement KeyChoice as of type Key Int, but I ran into troubles with this approach. I wonder if Dynamic or Type Families could achieve this, but I am quite at a loss and would like to hear your opinion. I did try to search for this a bit, but I don't quite know how to phrase my problem. I'd like to apologize in advance if this question has been asked already. Regards, Alexander Foremny

On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny
Hello list,
I am currently thinking that a problem of mine would best be solved if there was a Map-like data structure in which the value returned is parametrized over the lookup type.
I wonder is this makes sense and if such a data structure exists or if it could be created while still being well typed. I essentially want to statically define a scope of Key values and dynamically define a list of keys.
-- Scope of possible keys. type Label = String data Key a where KeyStr :: Label -> Key String KeyInt :: Label -> Key Int KeyChoice :: Label -> [a] -> Key a
-- Some key values, to be extended at runtime. strKey "Some String" strKey' "Another String" intKey "Some integer" choiceKey "Chose one" [ "a", "b", "c" ] :: KeyChoice String
Now I need a data structure to possibly associate a value to the key.
data MapG = ... type Value a = a insert :: Key a -> Value a -> MapG Key Value -> MapG Key Value lookup :: Key a -> MapG Key Value -> Maybe (Value a)
I tried implementing this with multiple Map k a's. I tried adding a phantom type on some storage type of to implement KeyChoice as of type Key Int, but I ran into troubles with this approach. I wonder if Dynamic or Type Families could achieve this, but I am quite at a loss and would like to hear your opinion.
I did try to search for this a bit, but I don't quite know how to phrase my problem. I'd like to apologize in advance if this question has been asked already.
Regards, Alexander Foremny
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
I think you might be looking for something like vault[1]. HTH, Michael [1] http://hackage.haskell.org/package/vault

Dear Michael,
thank you very much for your quick and interesting response. This
looks very much like what I want!
Regards,
Alexander Foremny
2012/7/31 Michael Snoyman
On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny
wrote: Hello list,
I am currently thinking that a problem of mine would best be solved if there was a Map-like data structure in which the value returned is parametrized over the lookup type.
I wonder is this makes sense and if such a data structure exists or if it could be created while still being well typed. I essentially want to statically define a scope of Key values and dynamically define a list of keys.
-- Scope of possible keys. type Label = String data Key a where KeyStr :: Label -> Key String KeyInt :: Label -> Key Int KeyChoice :: Label -> [a] -> Key a
-- Some key values, to be extended at runtime. strKey "Some String" strKey' "Another String" intKey "Some integer" choiceKey "Chose one" [ "a", "b", "c" ] :: KeyChoice String
Now I need a data structure to possibly associate a value to the key.
data MapG = ... type Value a = a insert :: Key a -> Value a -> MapG Key Value -> MapG Key Value lookup :: Key a -> MapG Key Value -> Maybe (Value a)
I tried implementing this with multiple Map k a's. I tried adding a phantom type on some storage type of to implement KeyChoice as of type Key Int, but I ran into troubles with this approach. I wonder if Dynamic or Type Families could achieve this, but I am quite at a loss and would like to hear your opinion.
I did try to search for this a bit, but I don't quite know how to phrase my problem. I'd like to apologize in advance if this question has been asked already.
Regards, Alexander Foremny
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
I think you might be looking for something like vault[1].
HTH, Michael

At first glance I noticed some problems with the vault library for my
particular approach.
Despite from being unique, Key values don't appear to carry any
information like the Label I need. However, it might be possible to
work around that.
The more grave problem seems to be that a Key cannot be
(de-)serialized. This might be impossible due to the type parameter a
in Key a.
However, it is no problem to fix the types of values to some finite collection.
Because of this some solution built around Dynamic seems to be more
and more appropriate. But I'll try to investigate vault further.
Regards,
Alexander Foremny
2012/7/31 Alexander Foremny
Dear Michael,
thank you very much for your quick and interesting response. This looks very much like what I want!
Regards, Alexander Foremny
2012/7/31 Michael Snoyman
: On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny
wrote: Hello list,
I am currently thinking that a problem of mine would best be solved if there was a Map-like data structure in which the value returned is parametrized over the lookup type.
I wonder is this makes sense and if such a data structure exists or if it could be created while still being well typed. I essentially want to statically define a scope of Key values and dynamically define a list of keys.
-- Scope of possible keys. type Label = String data Key a where KeyStr :: Label -> Key String KeyInt :: Label -> Key Int KeyChoice :: Label -> [a] -> Key a
-- Some key values, to be extended at runtime. strKey "Some String" strKey' "Another String" intKey "Some integer" choiceKey "Chose one" [ "a", "b", "c" ] :: KeyChoice String
Now I need a data structure to possibly associate a value to the key.
data MapG = ... type Value a = a insert :: Key a -> Value a -> MapG Key Value -> MapG Key Value lookup :: Key a -> MapG Key Value -> Maybe (Value a)
I tried implementing this with multiple Map k a's. I tried adding a phantom type on some storage type of to implement KeyChoice as of type Key Int, but I ran into troubles with this approach. I wonder if Dynamic or Type Families could achieve this, but I am quite at a loss and would like to hear your opinion.
I did try to search for this a bit, but I don't quite know how to phrase my problem. I'd like to apologize in advance if this question has been asked already.
Regards, Alexander Foremny
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
I think you might be looking for something like vault[1].
HTH, Michael

Would ixset or HiggsSet be suitable? http://hackage.haskell.org/package/ixsethttp://hackage.haskell.org/package/ixset-1.0.5 http://hackage.haskell.org/package/HiggsSet On Tue, Jul 31, 2012 at 12:56 PM, Alexander Foremny < alexanderforemny@gmail.com> wrote:
At first glance I noticed some problems with the vault library for my particular approach.
Despite from being unique, Key values don't appear to carry any information like the Label I need. However, it might be possible to work around that.
The more grave problem seems to be that a Key cannot be (de-)serialized. This might be impossible due to the type parameter a in Key a. However, it is no problem to fix the types of values to some finite collection.
Because of this some solution built around Dynamic seems to be more and more appropriate. But I'll try to investigate vault further.
Regards, Alexander Foremny
2012/7/31 Alexander Foremny
: Dear Michael,
thank you very much for your quick and interesting response. This looks very much like what I want!
Regards, Alexander Foremny
2012/7/31 Michael Snoyman
: On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny
wrote: Hello list,
I am currently thinking that a problem of mine would best be solved if there was a Map-like data structure in which the value returned is parametrized over the lookup type.
I wonder is this makes sense and if such a data structure exists or if it could be created while still being well typed. I essentially want to statically define a scope of Key values and dynamically define a list of keys.
-- Scope of possible keys. type Label = String data Key a where KeyStr :: Label -> Key String KeyInt :: Label -> Key Int KeyChoice :: Label -> [a] -> Key a
-- Some key values, to be extended at runtime. strKey "Some String" strKey' "Another String" intKey "Some integer" choiceKey "Chose one" [ "a", "b", "c" ] :: KeyChoice String
Now I need a data structure to possibly associate a value to the key.
data MapG = ... type Value a = a insert :: Key a -> Value a -> MapG Key Value -> MapG Key Value lookup :: Key a -> MapG Key Value -> Maybe (Value a)
I tried implementing this with multiple Map k a's. I tried adding a phantom type on some storage type of to implement KeyChoice as of type Key Int, but I ran into troubles with this approach. I wonder if Dynamic or Type Families could achieve this, but I am quite at a loss and would like to hear your opinion.
I did try to search for this a bit, but I don't quite know how to phrase my problem. I'd like to apologize in advance if this question has been asked already.
Regards, Alexander Foremny
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
I think you might be looking for something like vault[1].
HTH, Michael
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alp Mestanogullari

Another option which allows you to define your own key type is the dependent-map[1] package. It requires implementing some classes for your key type that encode a proof that key equality entails equality of the type indices. If the documentation is insufficient feel free to ask me for more details or examples.
[1] http://hackage.haskell.org/package/dependent-map
On Jul 31, 2012, at 6:56 AM, Alexander Foremny
At first glance I noticed some problems with the vault library for my particular approach.
Despite from being unique, Key values don't appear to carry any information like the Label I need. However, it might be possible to work around that.
The more grave problem seems to be that a Key cannot be (de-)serialized. This might be impossible due to the type parameter a in Key a. However, it is no problem to fix the types of values to some finite collection.
Because of this some solution built around Dynamic seems to be more and more appropriate. But I'll try to investigate vault further.
Regards, Alexander Foremny
2012/7/31 Alexander Foremny
: Dear Michael,
thank you very much for your quick and interesting response. This looks very much like what I want!
Regards, Alexander Foremny
2012/7/31 Michael Snoyman
: On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny
wrote: Hello list,
I am currently thinking that a problem of mine would best be solved if there was a Map-like data structure in which the value returned is parametrized over the lookup type.
I wonder is this makes sense and if such a data structure exists or if it could be created while still being well typed. I essentially want to statically define a scope of Key values and dynamically define a list of keys.
-- Scope of possible keys. type Label = String data Key a where KeyStr :: Label -> Key String KeyInt :: Label -> Key Int KeyChoice :: Label -> [a] -> Key a
-- Some key values, to be extended at runtime. strKey "Some String" strKey' "Another String" intKey "Some integer" choiceKey "Chose one" [ "a", "b", "c" ] :: KeyChoice String
Now I need a data structure to possibly associate a value to the key.
data MapG = ... type Value a = a insert :: Key a -> Value a -> MapG Key Value -> MapG Key Value lookup :: Key a -> MapG Key Value -> Maybe (Value a)
I tried implementing this with multiple Map k a's. I tried adding a phantom type on some storage type of to implement KeyChoice as of type Key Int, but I ran into troubles with this approach. I wonder if Dynamic or Type Families could achieve this, but I am quite at a loss and would like to hear your opinion.
I did try to search for this a bit, but I don't quite know how to phrase my problem. I'd like to apologize in advance if this question has been asked already.
Regards, Alexander Foremny
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
I think you might be looking for something like vault[1].
HTH, Michael
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Alexander Foremny wrote:
At first glance I noticed some problems with the vault library for my particular approach.
Despite from being unique, Key values don't appear to carry any information like the Label I need. However, it might be possible to work around that.
The more grave problem seems to be that a Key cannot be (de-)serialized. This might be impossible due to the type parameter a in Key a.
Vault is intended to be a store for values of any type, so it doesn't include any restriction on the type a in Key a . For reasons of type safety, this means that keys have to be abstract. You can't create a typed key from an untyped label alone, because this would allow you to coerce a value to a different type (just create two keys of different types from the same label).
However, it is no problem to fix the types of values to some finite collection.
That should work. You have to reify the type a in Key a in the value of the key. I think it's possible to use a data type family for the map type. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Hello, I made some trial and error with ghci to make it happy. I'm not
really sure this has the type safety you asked.
{-# LANGUAGE TypeFamilies, ExistentialQuantification, FlexibleContexts #-}
import Prelude hiding (lookup)
import Data.Typeable
class Typeable a => Key a where
type Value a :: *
data Assoc = forall a . (Typeable (Value a),Key a) => Assoc a (Value a)
insert :: (Typeable (Value a), Key a) => a -> Value a -> [Assoc] -> [Assoc]
insert k v = (Assoc k v :)
lookup :: (Typeable (Value a), Eq a, Key a) => a -> [Assoc] -> Value a
lookup k [] = error "noassoc"
lookup k ((Assoc k' v):xs) = case cast k' of
Nothing -> lookup k xs
Just k'' -> if k'' == k then case cast v of
Nothing -> error "nocast"
Just v' -> v'
else lookup k xs
I've tried without the typeclass with no luck.
For some reasons
type family Key a :: *
type family Value a :: *
and adding Typeable (Key a) to the contexts and Key 'a' in place of 'a'
leads to a lot of type errors.
Maybe it's possible with more help.
Hope I got it right.
Regards
paolino
2012/7/31 Alexander Foremny
Hello list,
I am currently thinking that a problem of mine would best be solved if there was a Map-like data structure in which the value returned is parametrized over the lookup type.
I wonder is this makes sense and if such a data structure exists or if it could be created while still being well typed. I essentially want to statically define a scope of Key values and dynamically define a list of keys.
-- Scope of possible keys. type Label = String data Key a where KeyStr :: Label -> Key String KeyInt :: Label -> Key Int KeyChoice :: Label -> [a] -> Key a
-- Some key values, to be extended at runtime. strKey "Some String" strKey' "Another String" intKey "Some integer" choiceKey "Chose one" [ "a", "b", "c" ] :: KeyChoice String
Now I need a data structure to possibly associate a value to the key.
data MapG = ... type Value a = a insert :: Key a -> Value a -> MapG Key Value -> MapG Key Value lookup :: Key a -> MapG Key Value -> Maybe (Value a)
I tried implementing this with multiple Map k a's. I tried adding a phantom type on some storage type of to implement KeyChoice as of type Key Int, but I ran into troubles with this approach. I wonder if Dynamic or Type Families could achieve this, but I am quite at a loss and would like to hear your opinion.
I did try to search for this a bit, but I don't quite know how to phrase my problem. I'd like to apologize in advance if this question has been asked already.
Regards, Alexander Foremny
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

This is without class :-)
{-# LANGUAGE TypeFamilies, ExistentialQuantification, FlexibleContexts #-}
import Prelude hiding (lookup)
import Data.Typeable
type family Value a :: *
data Assoc = forall a . (Typeable (Value a), Typeable a) => Assoc a (Value
a)
insert :: (Typeable (Value a), Typeable a) => a -> Value a -> [Assoc] ->
[Assoc]
insert k v = (Assoc k v :)
lookup :: (Typeable (Value a), Typeable a, Eq a) => a -> [Assoc] -> Value a
lookup k [] = error "noassoc"
lookup k ((Assoc k' v):xs) = case cast k' of
Nothing -> lookup k xs
Just k'' -> if k'' == k then case cast v of
Nothing -> error "nocast"
Just v' -> v'
else lookup k xs
*Main> type instance Value Integer = Char
*Main> type instance Value Int = String
*Main> let u = insert (1::Integer) 'c' $ insert (1::Int) "ciao" []
*Main> lookup (1 :: Integer) u
'c'
*Main> lookup (1 :: Int) u
"ciao"
*Main>
Regards
paolino
2012/8/1 Paolino
Hello, I made some trial and error with ghci to make it happy. I'm not really sure this has the type safety you asked.
{-# LANGUAGE TypeFamilies, ExistentialQuantification, FlexibleContexts #-}
import Prelude hiding (lookup) import Data.Typeable
class Typeable a => Key a where type Value a :: *
data Assoc = forall a . (Typeable (Value a),Key a) => Assoc a (Value a)
insert :: (Typeable (Value a), Key a) => a -> Value a -> [Assoc] -> [Assoc] insert k v = (Assoc k v :)
lookup :: (Typeable (Value a), Eq a, Key a) => a -> [Assoc] -> Value a lookup k [] = error "noassoc" lookup k ((Assoc k' v):xs) = case cast k' of Nothing -> lookup k xs Just k'' -> if k'' == k then case cast v of Nothing -> error "nocast" Just v' -> v' else lookup k xs
I've tried without the typeclass with no luck. For some reasons
type family Key a :: * type family Value a :: *
and adding Typeable (Key a) to the contexts and Key 'a' in place of 'a' leads to a lot of type errors. Maybe it's possible with more help.
Hope I got it right.
Regards paolino
2012/7/31 Alexander Foremny
Hello list,
I am currently thinking that a problem of mine would best be solved if there was a Map-like data structure in which the value returned is parametrized over the lookup type.
I wonder is this makes sense and if such a data structure exists or if it could be created while still being well typed. I essentially want to statically define a scope of Key values and dynamically define a list of keys.
-- Scope of possible keys. type Label = String data Key a where KeyStr :: Label -> Key String KeyInt :: Label -> Key Int KeyChoice :: Label -> [a] -> Key a
-- Some key values, to be extended at runtime. strKey "Some String" strKey' "Another String" intKey "Some integer" choiceKey "Chose one" [ "a", "b", "c" ] :: KeyChoice String
Now I need a data structure to possibly associate a value to the key.
data MapG = ... type Value a = a insert :: Key a -> Value a -> MapG Key Value -> MapG Key Value lookup :: Key a -> MapG Key Value -> Maybe (Value a)
I tried implementing this with multiple Map k a's. I tried adding a phantom type on some storage type of to implement KeyChoice as of type Key Int, but I ran into troubles with this approach. I wonder if Dynamic or Type Families could achieve this, but I am quite at a loss and would like to hear your opinion.
I did try to search for this a bit, but I don't quite know how to phrase my problem. I'd like to apologize in advance if this question has been asked already.
Regards, Alexander Foremny
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

First of all I'd like to thank everyone who participated in this
discussion! Most approaches look very promising, especially the last
is what I imagined, but were unable to write. Thanks for that,
especially.
I will try to solve my problem using these approaches and report back
once I succeed or run into trouble.
Regards,
Alexander Foremny
2012/8/1 Paolino
This is without class :-)
{-# LANGUAGE TypeFamilies, ExistentialQuantification, FlexibleContexts #-} import Prelude hiding (lookup) import Data.Typeable
type family Value a :: *
data Assoc = forall a . (Typeable (Value a), Typeable a) => Assoc a (Value a)
insert :: (Typeable (Value a), Typeable a) => a -> Value a -> [Assoc] -> [Assoc]
insert k v = (Assoc k v :)
lookup :: (Typeable (Value a), Typeable a, Eq a) => a -> [Assoc] -> Value a
lookup k [] = error "noassoc" lookup k ((Assoc k' v):xs) = case cast k' of Nothing -> lookup k xs Just k'' -> if k'' == k then case cast v of Nothing -> error "nocast" Just v' -> v' else lookup k xs
*Main> type instance Value Integer = Char *Main> type instance Value Int = String *Main> let u = insert (1::Integer) 'c' $ insert (1::Int) "ciao" [] *Main> lookup (1 :: Integer) u 'c' *Main> lookup (1 :: Int) u "ciao" *Main>
Regards paolino
2012/8/1 Paolino
Hello, I made some trial and error with ghci to make it happy. I'm not really sure this has the type safety you asked.
{-# LANGUAGE TypeFamilies, ExistentialQuantification, FlexibleContexts #-}
import Prelude hiding (lookup) import Data.Typeable
class Typeable a => Key a where type Value a :: *
data Assoc = forall a . (Typeable (Value a),Key a) => Assoc a (Value a)
insert :: (Typeable (Value a), Key a) => a -> Value a -> [Assoc] -> [Assoc] insert k v = (Assoc k v :)
lookup :: (Typeable (Value a), Eq a, Key a) => a -> [Assoc] -> Value a lookup k [] = error "noassoc" lookup k ((Assoc k' v):xs) = case cast k' of Nothing -> lookup k xs Just k'' -> if k'' == k then case cast v of Nothing -> error "nocast" Just v' -> v' else lookup k xs
I've tried without the typeclass with no luck. For some reasons
type family Key a :: * type family Value a :: *
and adding Typeable (Key a) to the contexts and Key 'a' in place of 'a' leads to a lot of type errors. Maybe it's possible with more help.
Hope I got it right.
Regards paolino
2012/7/31 Alexander Foremny
Hello list,
I am currently thinking that a problem of mine would best be solved if there was a Map-like data structure in which the value returned is parametrized over the lookup type.
I wonder is this makes sense and if such a data structure exists or if it could be created while still being well typed. I essentially want to statically define a scope of Key values and dynamically define a list of keys.
-- Scope of possible keys. type Label = String data Key a where KeyStr :: Label -> Key String KeyInt :: Label -> Key Int KeyChoice :: Label -> [a] -> Key a
-- Some key values, to be extended at runtime. strKey "Some String" strKey' "Another String" intKey "Some integer" choiceKey "Chose one" [ "a", "b", "c" ] :: KeyChoice String
Now I need a data structure to possibly associate a value to the key.
data MapG = ... type Value a = a insert :: Key a -> Value a -> MapG Key Value -> MapG Key Value lookup :: Key a -> MapG Key Value -> Maybe (Value a)
I tried implementing this with multiple Map k a's. I tried adding a phantom type on some storage type of to implement KeyChoice as of type Key Int, but I ran into troubles with this approach. I wonder if Dynamic or Type Families could achieve this, but I am quite at a loss and would like to hear your opinion.
I did try to search for this a bit, but I don't quite know how to phrase my problem. I'd like to apologize in advance if this question has been asked already.
Regards, Alexander Foremny
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (6)
-
Alexander Foremny
-
Alp Mestanogullari
-
Heinrich Apfelmus
-
James Cook
-
Michael Snoyman
-
Paolino