Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-08-02 Thread Alexander Foremny
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

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-08-01 Thread Heinrich Apfelmus
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

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-08-01 Thread 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

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-08-01 Thread 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

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread Michael Snoyman
On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny alexanderfore...@gmail.com 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

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread 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 mich...@snoyman.com: On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny alexanderfore...@gmail.com wrote: Hello list, I am

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread 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

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread Alp Mestanogullari
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 alexanderfore...@gmail.com wrote: At first glance I noticed some problems

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread James Cook
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