<div dir="ltr">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:<div><br></div><div><div>{-# LANGUAGE TypeOperators, DataKinds, TemplateHaskell, FlexibleContexts #-}</div><div>import Data.Extensible</div><div>import Control.Lens</div><div>import Control.Monad.State</div><div><br></div><div>mkField "foo bar baz"</div><div><br></div><div>statefulStuff :: State (Record '["foo" :> Int, "bar" :> Int, "baz" :> Float]) ()</div><div>statefulStuff = do</div><div>    v <- use foo</div><div>    bar += v</div><div>    baz .= 42</div><div><br></div><div><div>main = print $ execState statefulStuff<br></div><div>  $ foo @= 10 <: bar @= 0 <: baz @= 0 <: Nil</div></div><div><br></div><div>I could use Vector Any internally for O(1) lookup, but seems trade-off between lookup and update.</div><div><div class="gmail_extra"><br><div class="gmail_quote">2015-05-05 18:40 GMT+09:00 Alberto G. Corona <span dir="ltr"><<a href="mailto:agocorona@gmail.com" target="_blank">agocorona@gmail.com</a>></span>:<br><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left-width:1px;border-left-color:rgb(204,204,204);border-left-style:solid;padding-left:1ex"><div dir="ltr">Hi,<div><br></div><div>Anyone used some of the extensible record packages to create a kind of extensible state monad?</div><div><br></div><div>I mean something that besides having "get", "gets" and "put"  would have some kind of "add" and "gets":</div><div><br></div><div>add :: a -> State ()</div><div>gets  :: State (Maybe a)</div><div><br></div><div>or </div><div><br></div><div>add :: LabelName -> a -> State ()</div><div>gets :: LabelName -> State (Maybe a)</div><div><br></div><div><br></div><div><div>So that I can extend the state without using additional monad transformers. Monad transformers are very hard for beginners and scramble error messages</div><div><br></div><div>I 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.</div><div><br></div><div>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....</div><div><br></div><div>Anyone?</div><span class=""><font color="#888888">-- <br><div>Alberto.</div>
</font></span></div></div>
<br>_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a><br>
<br></blockquote></div><br></div></div></div></div>