Except the performance, my extensible[0] library provides native lens support (label names are also lenses!) and quite easy to use. Let me show an example:{-# LANGUAGE TypeOperators, DataKinds, TemplateHaskell, FlexibleContexts #-}import Data.Extensibleimport Control.Lensimport Control.Monad.StatemkField "foo bar baz"statefulStuff :: State (Record '["foo" :> Int, "bar" :> Int, "baz" :> Float]) ()statefulStuff = dov <- use foobar += vbaz .= 42main = print $ execState statefulStuff$ foo @= 10 <: bar @= 0 <: baz @= 0 <: NilI could use Vector Any internally for O(1) lookup, but seems trade-off between lookup and update.2015-05-05 18:40 GMT+09:00 Alberto G. Corona <agocorona@gmail.com>:_______________________________________________Hi,Anyone used some of the extensible record packages to create a kind of extensible state monad?I mean something that besides having "get", "gets" and "put" would have some kind of "add" and "gets":add :: a -> State ()gets :: State (Maybe a)oradd :: LabelName -> a -> State ()gets :: LabelName -> State (Maybe a)So that I can extend the state without using additional monad transformers. Monad transformers are very hard for beginners and scramble error messagesI did the first option for MFlow, hplayground and Transient packages (setSData and getSData). But my solution uses a map indexed by type and this requires a lookup for each access.I would like to know if there is an alternative with no lookups. I´m not obsessed with speed but In some applications the speed may be important....Anyone?--Alberto.
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe