Extensible states

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) or add :: 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 messages 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. 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.

On 05/05/15 12:40, Alberto G. Corona wrote:
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)
or
add :: 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 messages
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.
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?
If you care about the error message quality, you'd rather stay away from extensible records. And if you care about speed, most (all?) extensible records give you O(n) access, so you'd be actually better off with a simple (Hash)Map. Roman

On Tue, May 5, 2015 at 5:50 AM, Roman Cheplyaka
And if you care about speed, most (all?) extensible records give you O(n) access, so you'd be actually better off with a simple (Hash)Map.
Roman
https://github.com/fumieval/extensible is an example that is log n lookup, but it's not really clear (to me) that it would be faster for a real program since you might have small records only, and maybe other operations are slower.

Hello, I'm not sure if this is what you're looking for, but vinyl + lens state monad combinators let you write something like this: foo :: State (Rec Foo [B,C,F]) Bar foo = ... bar = State (Rec Foo [A,B,C,D,E,F] bar = do ... x <- zoom rsubset foo ... rlens SA .= 3 ... Unfortunately Vinyl has O(n) lookup (unless it gets optimized away by sufficiently glorious haskell compiler, I guess, but I have no idea whether it actually can happen). But I'm not sure if the speed impact is noticeable, compared to using monad transformer stacks, for example. http://hackage.haskell.org/package/vinyl http://hackage.haskell.org/package/vinyl-0.5.1/docs/Data-Vinyl-Lens.html http://hackage.haskell.org/package/lens https://www.fpcomplete.com/school/to-infinity-and-beyond/pick-of-the-week/a-... Best regards, Marcin Mrotek

Thanks all of you.
So there is no trick that can make extensible records O(1) for field
access, like the native haskell records?. I didn´t know that all the
extensible records have O(n) or O(log n) at most.
That is not better than my State monad with a Data.Map. It is not possible
to use HList-like records like the one that Adam mentioned since the type
signature must not change when a new field is added.
2015-05-05 22:20 GMT+02:00 Marcin Mrotek
Hello,
I'm not sure if this is what you're looking for, but vinyl + lens state monad combinators let you write something like this:
foo :: State (Rec Foo [B,C,F]) Bar foo = ...
bar = State (Rec Foo [A,B,C,D,E,F] bar = do ... x <- zoom rsubset foo ... rlens SA .= 3 ...
Unfortunately Vinyl has O(n) lookup (unless it gets optimized away by sufficiently glorious haskell compiler, I guess, but I have no idea whether it actually can happen). But I'm not sure if the speed impact is noticeable, compared to using monad transformer stacks, for example.
http://hackage.haskell.org/package/vinyl http://hackage.haskell.org/package/vinyl-0.5.1/docs/Data-Vinyl-Lens.html http://hackage.haskell.org/package/lens
https://www.fpcomplete.com/school/to-infinity-and-beyond/pick-of-the-week/a-...
Best regards, Marcin Mrotek
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
-- Alberto.

I think that the whole point of extensible records is to change the type on appending, to provide more safety at compile time than (hash) maps. If you don't want to use lenses (zoom) to combine different state monads, I guess a map is the best option.
Kind regards,
Marcin Mrotek
-----Wiadomość oryginalna-----
Od: "Alberto G. Corona "

Just as an afterthought about the O(n) lookup issue - extensible records are dependently typed versions of old, well-known data structures, so you always have a trade off between lookup and appending. In Haskell it's relatively easy to implement dependently typed lists (Vinyl, HList, etc), or maps (?) (apparently, Extensible linked by Adam, but I admit I haven't looked into the code). Dependently typed arrays are trickier. I guess it could be, for example, hacked around a (Vector Dynamic), then using (fromJust . fromDynamic) when it's certain at compile time that a there's a value of a certain type hidden in there, but I'm not sure if anyone has actually implemented it. They would necessarily have O(n) append, though. Best regards, Marcin Mrotek

I think there are many cases where some standard data type (that is not a list) is paired with type-level lists: I've tried the (unboxed) array case with http://code.haskell.org/HList/Data/HList/broken/RecordU.hs (worked with ghc 7.8), but it didn't seem to be any faster in my tests: I have a feeling that the index into the array should not be calculated as 1+1+1+1: the author of extensible does something that looks better. CTRex https://github.com/atzeus/CTRex does that dynamic+hash map idea. Another example is https://github.com/nikita-volkov/recordhttps https://github.com/nikita-volkov/record:// https://github.com/nikita-volkov/recordgithub.com https://github.com/nikita-volkov/record/ https://github.com/nikita-volkov/recordnikita-volkov https://github.com/nikita-volkov/record/record https://github.com/nikita-volkov/record using one data type for each length supported Just as an afterthought about the O(n) lookup issue - extensible records are dependently typed versions of old, well-known data structures, so you always have a trade off between lookup and appending. In Haskell it's relatively easy to implement dependently typed lists (Vinyl, HList, etc), or maps (?) (apparently, Extensible linked by Adam, but I admit I haven't looked into the code). Dependently typed arrays are trickier. I guess it could be, for example, hacked around a (Vector Dynamic), then using (fromJust . fromDynamic) when it's certain at compile time that a there's a value of a certain type hidden in there, but I'm not sure if anyone has actually implemented it. They would necessarily have O(n) append, though. Best regards, Marcin Mrotek

Okay, perhaps I'm too newbie to understand the big picture, but it seems to me you can get either: a) O(1) access to any, arbitrarily selected (at runtime) field b) O(1) append I guess option a) is better performance-wise, as appending is usually done less often than selecting (an O(1) slice is already possible with independently typed regular Haskell records) but dependently-typed-list-based implementation, or at the very least Vinyl (I haven't ever used HList) has the advantage of being dead simple in both implementation and usage. I mean, with Vinyl, you can write manual recursion over Rec's like: foo :: Rec ... -> Rec ... foo RNil = ... foo (r :& rs) = ... whenever GHC's typechecker gives up and goes on a strike; and I dare to say, with commonly used record sizes (have you ever used a record with more than, let's say, 10 fields?) the speed tradeoff is not noticeable. Don't get me wrong, I'm all in for cutting edge solutions like the one mentioned by Marcos, but I do think that rejecting the existing ones based on the non-constant time lookup is just premature optimisation. Best regards, Marcin Mrotek

Sorry, I meant: *O(1) slicing is already possible with independently typed regular Haskell VECTORS Best regards, Marcin Mrotek

Marcin Mrotek wrote:
Okay, perhaps I'm too newbie to understand the big picture, but it seems to me you can get either:
a) O(1) access to any, arbitrarily selected (at runtime) field b) O(1) append
I guess option a) is better performance-wise, as appending is usually done less often than selecting (an O(1) slice is already possible with independently typed regular Haskell records) but dependently-typed-list-based implementation, or at the very least Vinyl (I haven't ever used HList) has the advantage of being dead simple in both implementation and usage. I mean, with Vinyl, you can write manual recursion over Rec's like:
foo :: Rec ... -> Rec ... foo RNil = ... foo (r :& rs) = ...
whenever GHC's typechecker gives up and goes on a strike; and I dare to say, with commonly used record sizes (have you ever used a record with more than, let's say, 10 fields?) the speed tradeoff is not noticeable.
While more than 10 fields in a record is uncommon for typical library APIs and simple programs, real world projects can grow much larger records. One example is configuration data for complex programs (like Darcs or even GHC) with many options. It would be so nice if we could use record types for the configuration! Another application could in control system toolkits like EPICS [1], which currently has (actually: generates) C records with potentially hundreds of fields. If lookup is / remains linear we can never efficiently support these kinds of applications and that would be very sad. I think the most reasonable default is O(1) for lookup and O(n) for extension, like in Nikita Volkov's record package. It is quite unfortunate that this package limits the number of fields! If GHC would offer generic support for tuples of arbitrary size (with the same efficiency as today) this limitation could be avoided and all would be well. Cheers Ben [1] http://www.aps.anl.gov/epics/ -- "Make it so they have to reboot after every typo." ― Scott Adams

I somehow missed the preceding discussion, so I'll comment on what I've seen so far.
I think the most reasonable default is O(1) for lookup and O(n) for extension, like in Nikita Volkov's record package. It is quite unfortunate that this package limits the number of fields! If GHC would offer generic support for tuples of arbitrary size (with the same efficiency as today) this limitation could be avoided and all would be well.
Currently "record" is limited to up to 24 fields. However it was just an arbitrary number that I've chosen. No part of GHC limits us to that number. The only reason I'm not introducing bigger arities is that unfortunately the compilation time of the "record" library grows exponentially in relation to the highest arity supported. I expect, that limitation could be lifted once/if the ideas behind the library get implemented as an extension to GHC.

Nikita Volkov wrote:
I somehow missed the preceding discussion, so I'll comment on what I've seen so far.
I think the most reasonable default is O(1) for lookup and O(n) for extension, like in Nikita Volkov's record package. It is quite unfortunate that this package limits the number of fields! If GHC would offer generic support for tuples of arbitrary size (with the same efficiency as today) this limitation could be avoided and all would be well.
Currently "record" is limited to up to 24 fields. However it was just an arbitrary number that I've chosen. No part of GHC limits us to that number. The only reason I'm not introducing bigger arities is that unfortunately the compilation time of the "record" library grows exponentially in relation to the highest arity supported. I expect, that limitation could be lifted once/if the ideas behind the library get implemented as an extension to GHC.
Thanks for the clarification. So there is no hard limit in GHC, but we are (currently) limited by other factors. Some (more or less) minimal compiler support is, I guess, necessary to make any of the existing record libraries practical for real world programs. Cheers Ben -- "Make it so they have to reboot after every typo." ― Scott Adams

On 6 May 2015 at 00:03, Alberto G. Corona
Thanks all of you.
So there is no trick that can make extensible records O(1) for field access, like the native haskell records?. I didn´t know that all the extensible records have O(n) or O(log n) at most.
In principle it's possible to get O(1) access for extensible records. It depends on how undelying data layout. It's obviously not possible to have O(1) if record is build from ordinary ADT but if if record internally is array it is possible. Of course downside is appending is O(n) in that case

In the following paper we introduced an implementation that performs lookup
in O(log n) and insertion in O(1) by moving some of the work to compile
time.
@INPROCEEDINGS { MVP13,
AUTHOR = { Martinez, Bruno and Viera, Marcos and Pardo, Alberto },
TITLE = { Just Do It While Compiling!: Fast Extensible Records in
Haskell },
BOOKTITLE = { Proceedings of the ACM SIGPLAN 2013 Workshop on Partial
Evaluation and Program Manipulation },
SERIES = { PEPM '13 },
YEAR = { 2013 },
ISBN = { 978-1-4503-1842-6 },
LOCATION = { Rome, Italy },
PAGES = { 77--86 },
NUMPAGES = { 10 },
DOI = { 10.1145/2426890.2426908 },
ACMID = { 2426908 },
PUBLISHER = { ACM },
ADDRESS = { New York, NY, USA },
KEYWORDS = { balanced trees, extensible records, haskell, hlist, staged
computation, type-level programming },
PDF = { http://www.fing.edu.uy/~mviera/papers/pepm13.pdf },
}
Best,
marcos
On Tue, May 5, 2015 at 6:50 AM, Roman Cheplyaka
On 05/05/15 12:40, Alberto G. Corona wrote:
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)
or
add :: 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 messages
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.
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?
If you care about the error message quality, you'd rather stay away from extensible records.
And if you care about speed, most (all?) extensible records give you O(n) access, so you'd be actually better off with a simple (Hash)Map.
Roman
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

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.Extensible
import Control.Lens
import Control.Monad.State
mkField "foo bar baz"
statefulStuff :: State (Record '["foo" :> Int, "bar" :> Int, "baz" :>
Float]) ()
statefulStuff = do
v <- use foo
bar += v
baz .= 42
main = print $ execState statefulStuff
$ foo @= 10 <: bar @= 0 <: baz @= 0 <: Nil
I 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
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)
or
add :: 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 messages
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.
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

hmmm..
A form of "extensible state" constructed with an state monad with a Map
indexed by the type of the data using "typeOf" could have advantages over
extensible records. It makes the "transport" of data and the addition of
more kinds of data less cumbersome.
Among other things it encourages good programming practices like the use
of newtypes. It is just a matter of defining two primitives:
with getData :: (MonadState TheMap m,Typeable a) => m (Maybe a)
and setData :: (MonadState TheMap m, Typeable a) => a -> m ()
and perhaps a third : delData.
2015-05-08 7:33 GMT+02:00 Fumiaki Kinoshita
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.Extensible import Control.Lens import Control.Monad.State
mkField "foo bar baz"
statefulStuff :: State (Record '["foo" :> Int, "bar" :> Int, "baz" :> Float]) () statefulStuff = do v <- use foo bar += v baz .= 42
main = print $ execState statefulStuff $ foo @= 10 <: bar @= 0 <: baz @= 0 <: Nil
I 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
: 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)
or
add :: 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 messages
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.
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
-- Alberto.
participants (10)
-
adam vogt
-
Alberto G. Corona
-
Aleksey Khudyakov
-
Ben Franksen
-
Fumiaki Kinoshita
-
Marcin Mrotek
-
Marcos Viera
-
Nikita Volkov
-
Roman Cheplyaka
-
Silvio Frischknecht