Re: Make it possible to evaluate monadic actions when assigning record fields
apfelmus wrote: I see, the dreaded name-supply problem. Well, it just seems that monads are not quite the right abstraction for that one, right? (Despite that monads make up a good implementation). In other words, my opinion is that it's not the monadic code that is over-linearized but the code that is over-monadized. The main property of a "monad" for name-supply is of course f >> g = g >> f modulo alpha-conversion. Although we have to specify an order, it's completely immaterial. There _has_ to be a better abstraction than "monad" to capture this! I agree completely! It would be nice if the compiler could choose any order (or none at all, depending on implementation?) at its discretion. If serialization(where the gaps are filled with actual strings as names) produces different results depending on the order (similar to name-supply *monad*: not(f >> g = g >> f) in a too-significant way), we have a purity violation if the order is not well-defined. Big problem. So we need to make sure they are used in an abstracted enough manner - perhaps only an instance of Eq, to make sharing/uniqueness/identity detectable, no more. In dependently-typed languages I think we could have data structures that were fast but provably didn't depend in their operation on the material of ordering, for example, for lookup. Association-lists only need Eq but can be a little slow... So with this technique in Haskell, Frisby for example would examine the infinite tree starting at the returned root, and choose an order for internal use based on the shape of the tree (which represents a *cyclic* graph) -- it would be unable to use ordering provided by name-supply sequencing(monad). Which is just fine for it. (except for being O((number of rules)^2) to construct a parser, using association lists, I think.) Further abstraction could be added with a primitive UniqueNameMap of sorts, similar to (Map UniqueName a)... not enjoyable, so it might manage to be implemented in terms of some unsafe operations :-/. I hope my pessimism here is proved wrong :) Isaac ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Re: Make it possible to evaluate monadic actions when assigning record fields
apfelmus wrote: > In the end, I think that applicatively used monads are the wrong > abstraction. Simon Peyton-Jones wrote: > Can you be more explicit? Monadic code is often over-linearised. > I want to generate fresh names, say, and suddenly I have to name > sub-expressions. Not all sub-expressions, just the effectful ones. Neil Mitchell wrote: > The monad in question simply supplies free variables, so could be > applied in any order. I see, the dreaded name-supply problem. Well, it just seems that monads are not quite the right abstraction for that one, right? (Despite that monads make up a good implementation). In other words, my opinion is that it's not the monadic code that is over-linearized but the code that is over-monadized. The main property of a "monad" for name-supply is of course f >> g = g >> f modulo alpha-conversion. Although we have to specify an order, it's completely immaterial. There _has_ to be a better abstraction than "monad" to capture this! SPJ: > It'a a pain to define liftM_yes_no_yes which takes an effectful > argument in first and third position, and a non-effectful one as > the second arg: > > liftM_yes_no_yes :: (a->b->c->m d) > -> m a -> b -> m c -> m d > > What a pain. So we have either > > do { ...; va <- a; vc <- c; f va b vc; ... } > > or > do { ...; liftM_yes_no_yes f a b c; ...} > > or, with some syntactic sugar... > > do { ...; f $(a) b $(c); ...} > > The liftM solution is even more awkward if I want > > f (g $(a)) b c > > for example. (the last one is already a typo, i guess you mean f $(g $(a)) b c) Neil: > -- helpers, ' is yes, _ is no > > coreLet__ x y = f $ CoreLet x y > coreLet_' x y = f . CoreLet x =<< y > > coreLet x y = f $ CoreLet x y > > f (CoreApp (CoreLet bind xs) ys) = coreLet bind $(coreApp xs ys) > Uhm, but you guys know that while (m a -> a) requires the proposed syntactic sugar, (a -> m a) is easy? r = return elevateM f x1 = join $ liftM f x1 elevateM3 f x1 x2 x3 = join $ liftM3 f x1 x2 x3 do { ...; elevateM3 f a (r$ b) c; ...} elevateM3 f (elevateM g a) (r$ b) (r$ c) coreLet x y = liftM2 CoreLet x y >>= f g (CoreApp (CoreLet bind xs) ys) = coreLet (r$ bind) (coreApp xs ys) In other words, you can avoid creating special yes_no_yes wrappers by creating a yes_yes_yes wrapper and turning a no into a yes here and there. No need for turning yes into no. One could even use left-associative infix operators ($@) :: (a -> b) -> a -> b ($@@) :: Monad m => (m a -> b) -> a -> b ($@) = id ($@@) = id . return and currying elevateM3 f $@@ (elevateM g $@@ a) $@ b $@ c g (CoreApp (CoreLet bind xs) ys) = coreLet $@ bind $@@ coreApp xs ys The intention is that a (mixed!) sequence of operators should parse as f $@ x1 $@@ x2 $@ x3 = ((f $@ x1) $@@ x2) $@ x3 Leaving such games aside, the fact that yes_yes_yes-wrappers subsumes the others is a hint that types like NameSupply Expr -> NameSupply Expr -> NameSupply Expr are fundamental. In other words, the right type for expressions is probably not Expr but NameSupply Expr with the interpretation that the latter represents expressions with "holes" where the concrete names for variables are filled in. The crucial point is that holes may be _shared_, i.e. supplying free variable names will fill several holes with the same name. Put differently, the question is: how to share names without giving concrete names too early? I think it's exactly the same question as How to make sharing observable? This is a problem that haunts many people and probably every DSL-embedder (Lava for Hardware, Pan for Images, Henning Thielemann's work on sound synthesis, Frisby for parser combinators). In a sense, writing a Haskell compiler is similar to embedding a DSL. I have no practical experiences with the name-supply problem. So, the first question is: can the name-supply problem indeed be solved by some form of observable sharing? Having a concrete toy-language showing common patterns of the name-supply problem would be ideal for that. The second task would be to solve the observable sharing problem, _that_ would require some syntactic sugar. Currently, one can use MonadFix to "solve" it. Let's take parser combinators as an example. The left-recursive grammar digit -> 0 | .. | 9 number -> number' digit number' -> ε | number can be represented by something like mdo digit <- newRule $ foldr1 (|||) [0...9] number <- newRule $ number' &&& digit number' <- newRule $ empty ||| number This way, we can observe the sharing and break the left recursion. But of course, the monad is nothing more than syntactic sugar here, the order does not matter at all. What we really want to write is a custom let-expression let' digit = foldr1 (|||) [0..9] number = number' &&& digit number' = empty ||| number and still be able to observe sharing. SPJ: > I'm thinking of this as
Re: Re[2]: Make it possible to evaluate monadic actions when assigning record fields
Hi > This extension seems like a great idea - my only concern would be > about the order of computations. Clearly left-to-right makes sense, > but this may break some natural intuition in Haskell: i think that undefined order will be a best one Using "undefined" does not make for great reading in a standard! You just know that Hugs will pick right to left, Yhc will pick left to right, and GHC will offer a flag to choose between them ;) We have to pick, and there is only one logical choice - left to right. Thanks Neil ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Re[2]: Make it possible to evaluate monadic actions when assigning record fields
Hello Neil, Thursday, July 12, 2007, 3:10:10 PM, you wrote: > This extension seems like a great idea - my only concern would be > about the order of computations. Clearly left-to-right makes sense, > but this may break some natural intuition in Haskell: i think that undefined order will be a best one -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Re: Make it possible to evaluate monadic actions when assigning record fields
Hi Put differently, I don't see a compelling use-case for the proposed syntax extension. But I've seen many misused monads. A compelling use-case: http://darcs.haskell.org/yhc/src/libraries/core/Yhc/Core/Simplify.hs Look at coreSimplifyExprUniqueExt And from that file: -- helpers, ' is yes, _ is no coreCase__ x y = f $ CoreCase x y ; coreCase_' x y = f . CoreCase x =<< y coreLet__ x y = f $ CoreLet x y ; coreLet_' x y = f . CoreLet x =<< y coreLam__ x y = f $ CoreLam x y ; coreLam_' x y = f . CoreLam x =<< y coreApp__ x y = f $ CoreApp x y ; coreApp'_ x y = f . flip CoreApp y =<< x i.e. i've manually defined ' and _ variants to thread monadic effects through in quite horrible ways. The monad in question simply supplies free variables, so could be applied in any order. I think with this extension I can define: coreCase x y = f $ CoreCase x y coreLet x y = f $ CoreLet x y ... And taking just one rule, before: f (CoreApp (CoreLet bind xs) ys) = coreLet_' bind (coreApp__ xs ys) After: f (CoreApp (CoreLet bind xs) ys) = coreLet bind $(coreApp xs ys) Much nicer! This extension seems like a great idea - my only concern would be about the order of computations. Clearly left-to-right makes sense, but this may break some natural intuition in Haskell: flip f a b == f b a flip f $(a) $(b) /= f $(b) $(a) I don't think that is a show stopper though. Thanks Neil ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
RE: Make it possible to evaluate monadic actions when assigning record fields
| In the end, I think that applicatively used monads are the wrong | abstraction. For occasional use, liftM2 and `ap` often suffice. If the | applicative style becomes prevalent, then Applicative Functors are | likely to be the conceptually better choice. This is especially true | for | MonadReader. Arithmetic expressions are a case for liftM, too. And an | instance (Monad m, Num a) => Num (m a) allows to keep infix (+) and | (*). | | Put differently, I don't see a compelling use-case for the proposed | syntax extension. But I've seen many misused monads. Can you be more explicit? Monadic code is often over-linearised. I want to generate fresh names, say, and suddenly I have to name sub-expressions. Not all sub-expressions, just the effectful ones. It'a a pain to define liftM_yes_no_yes which takes an effectful argument in first and third position, and a non-effectful one as the second arg: liftM_yes_no_yes :: (a->b->c->m d) -> m a -> b -> m c -> m d What a pain. So we have either do { ...; va <- a; vc <- c; f va b vc; ... } or do { ...; liftM_yes_no_yes f a b c; ...} or, with some syntactic sugar... do { ...; f $(a) b $(c); ...} The liftM solution is even more awkward if I want f (g $(a)) b c for example. I'm thinking of this as a very superficial piece of syntactic sugar, aimed at avoiding the excessive linearization of monadic code. Nothing deep. Of course adding more syntactic sugar has a cost; but this one looks like having a good power to weight ratio. Simon ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Re: Make it possible to evaluate monadic actions when assigning record fields
Adde wrote: > apfelmus wrote: >> In any case, I'm *strongly against* further syntactic sugar for >> monads, including #1518. The more tiresome monads are, the more >> incentive you have to avoid them. > > Monads are a part of Haskell. The more tiresome monads are to use, the > more tiresome Haskell is to use. I suggest we leave the decision of > where and when to use them to each individual user of the language. Well, only the monads will remain as "tiresome" as they are now. Also, the most intriguing fact about monads (or rather about Haskell) is that they are not a (built-in) part of the language, they are "just" a type class. Sure, there is do-notation, but >>= is not much clumsier than that. In the end, I think that applicatively used monads are the wrong abstraction. For occasional use, liftM2 and `ap` often suffice. If the applicative style becomes prevalent, then Applicative Functors are likely to be the conceptually better choice. This is especially true for MonadReader. Arithmetic expressions are a case for liftM, too. And an instance (Monad m, Num a) => Num (m a) allows to keep infix (+) and (*). Put differently, I don't see a compelling use-case for the proposed syntax extension. But I've seen many misused monads. Regards, apfelmus ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Re: Make it possible to evaluate monadic actions when assigning record fields
Monads are a part of Haskell. The more tiresome monads are to use, the more tiresome Haskell is to use. I suggest we leave the decision of where and when to use them to each individual user of the language. /Adde > In any case, I'm *strongly against* further syntactic sugar for > monads, > including #1518. The more tiresome monads are, the more incentive you > have to avoid them. > > Regards, > apfelmus ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Re: Make it possible to evaluate monadic actions when assigning record fields
It is actually easy to play with this idea using Template Haskell, modulo some syntax. I implemented a little library called MEval last year that exports a TH preprocessing function meval :: Meval a => Q a -> Q a and a "magic" variable p :: Monad m => m a -> a The preprocessing function will perform Greg's translation whenever it finds Meval.p applied to something inside a do statement. I find this approach useful especially when you want to evaluate monadic arguments inside arithmetic expressions or infix expressions in general. Then, the combinator approach provided with Control.Applicative tends to obscure the expressions. Other examples are case and if expressions in which you want to scrutinize monadic expressions. I attach a tar file with the library and an example program, feel free to hack away on them. Cheers, Magnus Simon Peyton-Jones wrote: > Another alternative (which I got from Greg Morrisett) that I'm toying with is > this. It's tiresome to write > > do { x <- >; y <- >; f x y } > > In ML I'd write simply > > f > > So Greg's idea (or at least my understanding thereof) is to write it like > this: > > do { f $(stuff1) $(stuff2) } > > The idea is that a "splice" $e must be lexically enclosed by a 'do', with no > intervening lambda. It's desugared to the code above; that is, each splice > it pulled out, in lexically left-right order, and given a name, which > replaces the splice. > > Of course it doesn't have to look like the above; the rule applies to any do: > > do { v <- this; foo $(h v); y <- f $(t v v); ...etc } > > The "linearise the splices" rule is quite general. > > Don't burn any cycles on concrete syntax; I know the $ notation is used for > Template Haskell; one would need to think of a good syntax. But the idea is > to make it more convenient to write programs that make effectful calls, and > then use the result exactly once. > > Anyway, this'd do what the original proposer wanted, but in a much more > general way. > > Just a thought -- I have not implemented this. > > Simon > > | -Original Message- > | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Adde > | Sent: 10 July 2007 21:40 > | To: [EMAIL PROTECTED] > | Cc: haskell-prime@haskell.org > | Subject: Re: Make it possible to evaluate monadic actions when assigning > record fields > | > | On Tue, 2007-07-10 at 17:04 +, [EMAIL PROTECTED] wrote: > | > Isaac Dupree <[EMAIL PROTECTED]> wrote: > | > > > | > > Adde wrote: > | > > > tmp <- foo > | > > > return Bar { > | > > >barFoo = tmp > | > > > } > | > > > | > > There is a feature being worked on in GHC HEAD that would let you do > | > > > | > > do > | > >tmp <- foo > | > >return Bar{..} > | > > > | > > which captures fields from everything of the same name that's in scope. > | > > I think this would also satisfy your desire. > | > > > | > > | > I guess this means I could write: > | > > | > > | > data D = C {field1 :: Bool, field2 :: Char} > | > > | > f x = do > | > field1 <- foo1 > | > field2 <- foo2 > | > field3 <- foo3 > | > other stuff > | > return C{..} > | > > | > > | > instead of > | > > | > > | > f x = do > | > tmp1 <- foo1 > | > tmp2 <- foo2 > | > field3 <- foo3 > | > other stuff > | > return $ C { field1 = tmp1, field2 = tmp2 } > | > > | > > | > This has a dangerous feel to it --- > | > extending the definition of D to include a field field3 > | > may have quite unintended consequences. > | > > | > > | > What I am missing most in the record arena > | > is a functional notation for record update, for example: > | > > | > {^ field1 } = \ f r -> r {field1 = f (field1 r)} > | > | I agree, capturing variables without asking is just scary. > | While I'm pretty biased I still think my suggestion solves the problem > | in a cleaner, more consistent way. > | > | /Adde > | > | ___ > | Haskell-prime mailing list > | Haskell-prime@haskell.org > | http://www.haskell.org/mailman/listinfo/haskell-prime MEval.tar.gz Description: GNU Zip compressed data ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Re: Make it possible to evaluate monadic actions when assigning record fields
ctm: > Indeed it can. Ignoring conventional wisdom about dirty linen, here are > idiom brackets > > > class Applicative i => Idiomatic i f g | g -> f i where > > idiomatic :: i f -> g > > > iI :: Idiomatic i f g => f -> g > > iI = idiomatic . pure > > > data Ii = Ii > > > instance Applicative i=> Idiomatic i x (Ii -> i x) where > > idiomatic xi Ii = xi > > instance Idiomatic i f g => Idiomatic i (s -> f) (i s -> g) where > > idiomatic sfi si= idiomatic (sfi <*> si) > > So that > > iI f x y Ii = f <$> x <*> y > > Now add > > > data Ji = Ji > > > instance (Monad i, Applicative i)=> Idiomatic i (i x) (Ji -> i > x) where > > idiomatic xii Ji = join xii > > and you've got > > iI f x y Ji = join $ f <$> x <*> y Very nice! Just so we don't forget this, I created a wiki page, http://haskell.org/haskellwiki/Idiom_brackets -- Don ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Re: Make it possible to evaluate monadic actions when assigning record fields
Hi On 11 Jul 2007, at 11:13, apfelmus wrote: Wouter Swierstra wrote: Using Control.Applicative you could already write: f <$> x <*> y No, since f is not a pure function, it's f :: x -> y -> m c. The correct form would be join $ f <$> x <*> y (Why doesn't haddock document infix precedences?) But maybe some type-class hackery can be used to eliminate the join. Indeed it can. Ignoring conventional wisdom about dirty linen, here are idiom brackets > class Applicative i => Idiomatic i f g | g -> f i where > idiomatic :: i f -> g > iI :: Idiomatic i f g => f -> g > iI = idiomatic . pure > data Ii = Ii > instance Applicative i=> Idiomatic i x (Ii -> i x) where > idiomatic xi Ii = xi > instance Idiomatic i f g => Idiomatic i (s -> f) (i s -> g) where > idiomatic sfi si= idiomatic (sfi <*> si) So that iI f x y Ii = f <$> x <*> y Now add > data Ji = Ji > instance (Monad i, Applicative i)=> Idiomatic i (i x) (Ji -> i x) where > idiomatic xii Ji = join xii and you've got iI f x y Ji = join $ f <$> x <*> y or, more flexibly, > data J = J > instance (Monad i, Idiomatic i f g) => Idiomatic i (i f) (J -> g) where > idiomatic fii J = idiomatic (join fii) so you can insert joins wherever you like, thus: iI f x y J z Ii = join (f <$> x <*> y) <*> z = do {x' <- x; y' <- y; f' <- f x y; z' <- z; return (f' z')} Of course, the implementation is an ugly hack, made uglier still by ASCII. Worse, for reasons I have never entirely understood, the type-class hackery doesn't allow these brackets to nest as they should. Even so, I find them a considerable convenience. I always assumed that was down to peculiarity on my part. I thought I'd present it as a curio illustrating part of the design space, but I don't imagine there's that big a market for an "idiom brackets done properly" proposal. All the best Conor ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Re[2]: Make it possible to evaluate monadic actions when assigning record fields
Hello Simon, Wednesday, July 11, 2007, 11:38:31 AM, you wrote: > So Greg's idea (or at least my understanding thereof) is to write it like > this: > do { f $(stuff1) $(stuff2) } Simon, it is thing i dreamed for a years! Haskell has serious drawback for imperative programming compared to C - each action should be written as separate statement and this makes program too wordy - just try to rewrite something like x[i] += y[i]*z[i] in Haskell i need a way to perform actions and read data values inside calculations. there are two possible ways: * write pure expressions like we do in C and let's ghc guess yourself where evaluation should be added: x <- newIORef 1 y <- newIORef 1 z <- newIORef 1 f x (y*z) this means that any expression of type IORef a or IO a automatically translated into evaluation. the same should work for arrays, hashes and so on, so it probably should be a class. the problem, of course, is that IO/IORef/.. is a first class values so it's hard to distinguish where it should be evaluated and where used as is. another problem is its interaction with type inference - we may not know which concrete type this expression has * add an explicit operation which evaluates data, as you suggests. again, it should be a class which allows to add evaluation support for hashes/... actually, ML has something similar - it uses "." operation to evaluate variable values = and, while we on this topic, another problem for imperative programming style usability is control structures. how we can rewrite the following: delta=1000 while (delta>0.01) x = ... if (x<0) break delta = abs(n-x*x) = btw, proposal of "prefix expressions" also simplifies imperative programs a bit: now we should write something like this: when (a>0) $ do . while this proposal allows to omit "$" and make program look a bit more natural = one more complaint: the syntax for list $ \item -> do doesn't look too natural compared to other languages. it will be great to write it as for item in list do - of course, with 'for' still a plain function defined by user = may be, i should collect all these ideas on "imperative programming" page? -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Re: Make it possible to evaluate monadic actions when assigning record fields
Wouter Swierstra wrote: > > On 11 Jul 2007, at 08:38, Simon Peyton-Jones wrote: > >> Another alternative (which I got from Greg Morrisett) that I'm toying >> with is this. It's tiresome to write >> >> do { x <- >>; y <- >>; f x y } >> >> In ML I'd write simply >> >> f > > Using Control.Applicative you could already write: > > f <$> x <*> y No, since f is not a pure function, it's f :: x -> y -> m c. The correct form would be join $ f <$> x <*> y (Why doesn't haddock document infix precedences?) But maybe some type-class hackery can be used to eliminate the join. In any case, I'm *strongly against* further syntactic sugar for monads, including #1518. The more tiresome monads are, the more incentive you have to avoid them. Regards, apfelmus ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Re: Make it possible to evaluate monadic actions when assigning record fields
On 11 Jul 2007, at 08:38, Simon Peyton-Jones wrote: Another alternative (which I got from Greg Morrisett) that I'm toying with is this. It's tiresome to write do { x <- ; y <- ; f x y } In ML I'd write simply f Using Control.Applicative you could already write: f <$> x <*> y I don't see the immediate need for more syntactic sugar - this is about as concise as it can get and it does not require compiler extensions. All the best, Wouter This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation. ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
RE: Make it possible to evaluate monadic actions when assigning record fields
Another alternative (which I got from Greg Morrisett) that I'm toying with is this. It's tiresome to write do { x <- ; y <- ; f x y } In ML I'd write simply f So Greg's idea (or at least my understanding thereof) is to write it like this: do { f $(stuff1) $(stuff2) } The idea is that a "splice" $e must be lexically enclosed by a 'do', with no intervening lambda. It's desugared to the code above; that is, each splice it pulled out, in lexically left-right order, and given a name, which replaces the splice. Of course it doesn't have to look like the above; the rule applies to any do: do { v <- this; foo $(h v); y <- f $(t v v); ...etc } The "linearise the splices" rule is quite general. Don't burn any cycles on concrete syntax; I know the $ notation is used for Template Haskell; one would need to think of a good syntax. But the idea is to make it more convenient to write programs that make effectful calls, and then use the result exactly once. Anyway, this'd do what the original proposer wanted, but in a much more general way. Just a thought -- I have not implemented this. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Adde | Sent: 10 July 2007 21:40 | To: [EMAIL PROTECTED] | Cc: haskell-prime@haskell.org | Subject: Re: Make it possible to evaluate monadic actions when assigning record fields | | On Tue, 2007-07-10 at 17:04 +, [EMAIL PROTECTED] wrote: | > Isaac Dupree <[EMAIL PROTECTED]> wrote: | > > | > > Adde wrote: | > > > tmp <- foo | > > > return Bar { | > > >barFoo = tmp | > > > } | > > | > > There is a feature being worked on in GHC HEAD that would let you do | > > | > > do | > >tmp <- foo | > >return Bar{..} | > > | > > which captures fields from everything of the same name that's in scope. | > > I think this would also satisfy your desire. | > > | > | > I guess this means I could write: | > | > | > data D = C {field1 :: Bool, field2 :: Char} | > | > f x = do | > field1 <- foo1 | > field2 <- foo2 | > field3 <- foo3 | > other stuff | > return C{..} | > | > | > instead of | > | > | > f x = do | > tmp1 <- foo1 | > tmp2 <- foo2 | > field3 <- foo3 | > other stuff | > return $ C { field1 = tmp1, field2 = tmp2 } | > | > | > This has a dangerous feel to it --- | > extending the definition of D to include a field field3 | > may have quite unintended consequences. | > | > | > What I am missing most in the record arena | > is a functional notation for record update, for example: | > | > {^ field1 } = \ f r -> r {field1 = f (field1 r)} | | I agree, capturing variables without asking is just scary. | While I'm pretty biased I still think my suggestion solves the problem | in a cleaner, more consistent way. | | /Adde | | ___ | Haskell-prime mailing list | Haskell-prime@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-prime ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Re: Make it possible to evaluate monadic actions when assigning record fields
On Tue, 2007-07-10 at 17:04 +, [EMAIL PROTECTED] wrote: > Isaac Dupree <[EMAIL PROTECTED]> wrote: > > > > Adde wrote: > > > tmp <- foo > > > return Bar { > > >barFoo = tmp > > > } > > > > There is a feature being worked on in GHC HEAD that would let you do > > > > do > >tmp <- foo > >return Bar{..} > > > > which captures fields from everything of the same name that's in scope. > > I think this would also satisfy your desire. > > > > I guess this means I could write: > > > data D = C {field1 :: Bool, field2 :: Char} > > f x = do > field1 <- foo1 > field2 <- foo2 > field3 <- foo3 > other stuff > return C{..} > > > instead of > > > f x = do > tmp1 <- foo1 > tmp2 <- foo2 > field3 <- foo3 > other stuff > return $ C { field1 = tmp1, field2 = tmp2 } > > > This has a dangerous feel to it --- > extending the definition of D to include a field field3 > may have quite unintended consequences. > > > What I am missing most in the record arena > is a functional notation for record update, for example: > > {^ field1 } = \ f r -> r {field1 = f (field1 r)} I agree, capturing variables without asking is just scary. While I'm pretty biased I still think my suggestion solves the problem in a cleaner, more consistent way. /Adde ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Re: Make it possible to evaluate monadic actions when assigning record fields
Isaac Dupree <[EMAIL PROTECTED]> wrote: > > Adde wrote: > > tmp <- foo > > return Bar { > >barFoo = tmp > > } > > There is a feature being worked on in GHC HEAD that would let you do > > do >tmp <- foo >return Bar{..} > > which captures fields from everything of the same name that's in scope. > I think this would also satisfy your desire. > I guess this means I could write: data D = C {field1 :: Bool, field2 :: Char} f x = do field1 <- foo1 field2 <- foo2 field3 <- foo3 other stuff return C{..} instead of f x = do tmp1 <- foo1 tmp2 <- foo2 field3 <- foo3 other stuff return $ C { field1 = tmp1, field2 = tmp2 } This has a dangerous feel to it --- extending the definition of D to include a field field3 may have quite unintended consequences. What I am missing most in the record arena is a functional notation for record update, for example: {^ field1 } = \ f r -> r {field1 = f (field1 r)} ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Re: Make it possible to evaluate monadic actions when assigning record fields
Adde wrote: tmp <- foo return Bar { barFoo = tmp } There is a feature being worked on in GHC HEAD that would let you do do tmp <- foo return Bar{..} which captures fields from everything of the same name that's in scope. I think this would also satisfy your desire. (also, the liftM approach doesn't let you choose the order of the monadic actions.) Isaac ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Make it possible to evaluate monadic actions when assigning record fields
Hi, I'm forwarding this feature request as is on the advice of Neil Mitchel for discussion / possible inclusion in future versions of Haskell. #1518: Make it possible to evaluate monadic actions when assigning record fields (<-) -+-- Reporter: [EMAIL PROTECTED] | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler|Version: 6.6.1 Severity: normal | Keywords: Difficulty: Unknown | Os: Unknown Testcase: | Architecture: Unknown -+-- It is currently not possible to build records from values resulting from monadic actions while still using the field-specifiers. foo :: IO Int ... data Bar = Bar { barFoo :: Int } buildBar :: IO () buildBar = do return Bar { barFoo <- foo --Evaluate foo to get the Int-value } I've found two possible ways of doing this: 1) Using temporaries to evaluate the actions before assigning which doubles the number of lines: tmp <- foo return Bar { barFoo = tmp } 2) Lifting the record constructor which prevents you from using field specifiers (and you really need field specifiers when dealing with larger records): liftM Bar foo Thanks, Adde ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime