!standard 6.9(0) 16-10-06 AI12-0197-3/02 !class Amendment 16-10-05 !status Hold (9-0-1) - 18-06-22 !status work item 16-10-05 !status received 16-10-05 !priority Very Low !difficulty Hard !subject generator functions !summary ** TBD. !problem The expression of computation often works on streams of data. It is often necessary to express computation of streams as incremental routines, working on chunks of data. But expressing algorithms in an incremental fashion is difficult: It implies manually keeping and maintaining the state of your algorithm, saving it on exit, and restoring it on re-entry. Generators, often called resumable functions, or Iterators in C#, offer a way to write such incremental code in a straightforward procedural way, by giving you the possibility to resume a function after it has returned. This resumable return capability is generally called "yield" in other languages, so we will use the same terminology in this AI. Ada offers a similar capability via the way of tasks and rendez-vous. However, tasks have certain properties that are not always desirable: 1. Non-determinism. Tasks execution is preemptive and thus non-deterministic. It means that any access to non-synchronized outer variables is non safe by default. Non determinism also implies that the resulting code and runtime are much harder to certify and that it is harder to prove any properties about them. 2. Synchronization overhead. This stems from point 1, but when you need a deterministic synchronization point, you'll pay for it in performance. Assorted is the general overhead of starting/stopping a task for short lived iterators. !proposal We propose introducing a new kind of type, called a generator type. This new kind of type will have special attributes who allow incremental execution of the body. The body will be allowed to "yield" values via a new kind of statement, the yield statement. Here is an example of what such a type declaration would look like: generator type Prime_Factory (Sieve_Size : Natural) yield Positive with Post => Prime_Factory'Next'Result <= Sieve_Size; generator body Prime_Factory (Sieve_Size : Natural) yield Positive is Is_Composite : array (2 .. Sieve_Size) of Boolean := (others => False); Current : Integer range Is_Composite'Range := 2; procedure Mark_Multiples (Prime : Positive) is Multiple : Positive := Prime; begin while Multiple <= Sieve_Size - Prime loop Multiple := Multiple + Prime; Is_Composite (Multiple) := True; end loop; end Mark_Multiples; begin while Current <= Sieve_Size loop if not Is_Composite (Current) then Mark_Multiples (Prime => Current); yield Current; end if; Current := Current + 1; end loop; end Prime_Factory; This type could then be instantiated and used in the following way: P : Prime_Factory (1000); while Not_Enough_Prime_Numbers loop if P'Yielding then Put_Line ("Next prime number is " & P'Next'Image); end if; end loop; As shown, clients interact with generator instances via the use of the 'Next and 'Yielding attributes. 'Next means "run until reaching either a yield statement or the end of the generator body; if the former, then execute the yield statement and return the given result; if the latter then raise Program_Error". The type returned by the 'Next attribute is the type after the yield in the generator declaration. 'Yielding means "run until reaching either a yield statement or the end of the generator body; return False if and only if a yield statement is reached (the yield statement is not executed in this case)." In other words, 'Yielding indicates whether it is ok to call Next. A generator type is subject to the following constraints: 1. Have to contain at least one yield statement. 2. Can contain return statements, as long as they have no expressions, in order to allow the user to terminate the execution early. We also allow yield statements to be contained by procedure directly or indirectly nested in the body of the generator. There are two yield statements, the regular one and the extended yield statement, as for return statements, and for the same reasons, namely build-in-place and limited types. Another way of consuming the generator is via the for .. of loop: P : Prime_Factory (1000); for Prime_Number of P loop Put_Line ("Next prime number is " & Prime_Number'Image) end loop; This is syntax sugar that will be expanded to the former form. If an exception is raised in the generator while it is executing, subsequently to a call to the ‘Next attribute, the generator is finalized, and the exception is propagated into the caller of the ‘Next attribute. We also propose introducing a second kind of generator type, called an abstract generator type: type Positive_Generator yield Positive; Abstract generator types are generator types for which we only know the yielded type, but not the implementation. This means that: 1. Those types don't have a body. 2. They're indefinite. 3. Specific generator implementations, such as the one above, can be converted to abstract generator types, with rules closely following the rules to convert specific tagged types to classwide types, with the added rule that you can convert any specific generator type to any abstract generator type, provided the yielded subtype statically matches. The accessibility rules will be the same, as well as the implicit conversion rules. This means that: -- This is illegal regarding accessibility rules. type Positive_Generator yield Positive; type Ref is access Positive_Generator; Ptr : Ref; procedure P is generator type Local_Generator is ...; function F yield Local_Generator is ...; begin Ptr := new Local_Generator'(F); -- This is legal regarding conversion rules type Positive_Generator yield Positive; generator type Foo yield Positive; ... F : Foo; G : Positive_Generator := F; 4. 'Next and 'Yielding operations on instances/views of abstract generator types are dispatching. It is proposed that generators be non-synchronized entities: Nothing will be done to prevent unsynchronized access, and if the user wants to use one from several tasks concurrently, it shall be possible, but the user would have to wrap the generator in a protected object, or another synchronized construct. Syntax We propose introducing two new keywords, "yield" and "generator". We propose introducing these new declarations: generator_type_declaration ::= "generator" "type" defining_identifier [known_discriminant_part] "yield" subtype_indication generator_type_body ::= "generator" "type" defining_identifier [known_discriminant_part] "yield" subtype_indication "is" declarative_part "begin" handled_sequence_of_statements "end" [designator] abstract_generator_type ::= "type" defining_identifier "yield" subtype_indication and two new statements: yield_statement ::= "yield" expression ";" extended_yield_statement ::= "yield" extended_return_object_declaration "do" handled_sequence_of_statements "end" "yield" ##implementation note While it might be possible to implement a limited version of this feature using only code rewritings and the existing runtime support, the recommended approach is a mix of both: 1. Expose a runtime capability for context switching, eg. saving the state of the stack, registers, and other local information, and restoring it. 2. Do simple expansion phases to expand from the high-level generator code to a version using the runtime support. In that scheme, the following code: generator type Prime_Numbers yield Integer; generator body Prime_Numbers yield Integer is I : Integer := 0; begin loop if Is_Prime (I) then yield I; end if; I := I + 1; end loop; end Even; could be expanded to this code: package Int_Generators_Impl is new Generators (Integer); type Prime_Numbers_Generator is new Int_Generators_Impl.Object with null record; overriding procedure Generate (D : in out Prime_Numbers_Generator; Context : Int_Generators_Impl.Context) is I : Integer := 0; begin loop if Is_Prime (I) then Context.Yield (I); end if; I := I + 1; end loop; end Generate; Note that this code is already working code, using a runtime library that was developed on top of a portable stack switching library called PCL. Not shown would be the code wrapping the implementation specific generator object into a Ada.Containers.Generators object and calling the appropriate operation when an item is requested. !wording ** TBD. !discussion # Nested yield statements issues It is strongly believed that we should allow yield statements in nested procedures in the generator. However, this might cause some problems, if an access to such a procedure is passed, and then called in an execution context that is not the one of the original generator. As usual with those kind of problems, we have two class of solutions: 1. Dynamically disallow that, at run-time. 2. Try to disallow that statically, by, for example, transitively forbidding access to procedures containing yield statements, or calling such procedures. Another issue raised by nested yield statements and extended yield statements is that you can yield inside of a yield, which should raise an exception: procedure Foo is begin ... yield (); end; begin Foo; -- ok yield X : T do ...; Foo; -- This should raise P_E end; # Generator singletons Since generators are very much like tasks, we probably want to allow to declare singleton generators like that: generator Foo yield Positive; generator body Foo yield Positive is begin yield 12; end Foo; # Omit declaration Although it is not allowed with tasks, in the interest of brevity/not repeating yourself, it has been considered that it should be possible to omit the declaration of a generator in some simple cases, as it is possible with subprograms. To keep it simple and non ambiguous, we propose to make declaration optional for singletons, but mandatory for types: generator body Foo yield Positive is -- This is implicitly a singleton begin yield 12; end Foo; generator Foo yield Positive; generator body Foo yield Positive is -- This is explicitly a singleton begin yield 12; end Foo; generator type Foo yield Positive; generator body Foo yield Positive is -- This is explicitly a type begin yield 12; end Foo; # Generators vs. passive tasks The benefits provided by generators can also be provided by a construct called passive tasks. Generally, a lot of use cases for generators are translatable in a way or another in terms of tasking, so we expect still a lot of the discussion will be around that issue. # Runtime support vs. rewriting into sequential code An approach entirely based on rewriting user code into code using callbacks would be problematic when combining separate compilation, and generators being passed around by subprograms, or more generally in presence of dispatching programs returning generators. package A is function Foo return Int_Generators.Generator; end A; package B is procedure Bar (G : Int_Generators.Generator); end B; Since here, the actual implementation wrapped by the generator object might vary, rewriting will not be possible in every case. Forcing the users to have a specific type for every generator instance, rather than allowing a general type depending on the yield type, would allow rewriting, but it would still be complicated to do separate compilation (akin to generic expansion), and abstraction would be lost along the way (no possibility to to have ad-hoc polymorphism on different generators having the same yield type) # Generators receiving values In some (not all) implementations of generators, generators are able to be passed values when their control is restored. It might be interesting to: 1. Think about what such a feature might look like in Ada 2. Try and conceive the initial feature in a way that allows extension to support this at a later stage. This won't be covered in this proposal though, because it is thought that the feature as proposed is ambitious enough for an initial revision. !examples ** TBD. !ASIS ** TBD. !ACATS test An massive set of ACATS B-Test and C-Tests are needed to check that the new capabilities are supported. !appendix From: Steve Baird Sent: Wednesday, September 7, 2016 6:49 PM One of my homework items from Pisa was to propose alternative syntax for generators (AI12-0197). So here is my very informal proposal. After some very helpful discussions with Raphael and Florian, I think we need two forms of generator types, somewhat like the distinction between a task type and a task interface type. One form is tied to a specific implementation (i.e., it has a body) and uses syntax similar to the existing syntax for task types and protected types (but with a new keyword). All generator types of both forms are limited. An example of the first form: generator type Prime_Factory (Sieve_Size : Natural) yield Positive with Post => Prime_Factory'Next'Result <= Sieve_Size; generator body Prime_Factory is Is_Composite : array (2 .. Sieve_Size) of Boolean := (others => False); Current : Integer range Is_Composite'Range := 2; procedure Mark_Multiples (Prime : Positive) is Multiple : Positive := Prime; begin while Multiple <= Sieve_Size - Prime loop Multiple := Multiple + Prime; Is_Composite (Multiple) := True; end loop; end Mark_Multiples; begin while Current <= Sieve_Size loop if not Is_Composite (Current) then Mark_Multiples (Prime => Current); yield Current; end if; Current := Current + 1; end loop; end Prime_Factory; Clients use 'Next and 'Yielding attributes. 'Next means "run until reaching either a yield statement of the end of the generator body; if the former, then execute the yield statement and return the given result; if the latter then raise P_E". 'Yielding is defined on these guys and means "run until reaching either a yield statement or the end of the generator body; return False if and only if a yield statement is reached (the yield statement is not executed in this case)." In other words, 'Yielding indicates whether it is ok to call Next. 'Terminated was considered instead of 'Yielding (albeit with the opposite polarity), but it seemed odd that querying 'Terminated could have a side effect. A generator object executes/elaborates nothing until either 'Next or 'Terminated is queried. In particular, it does nothing during its default initialization (and there is nothing analogous to task activation for these guys). You can have extended yield statements: yield X : T do Counter := Counter + 1; X.Field := Counter; end yield; These are needed for the same reasons as extended return statements (notably, support for limited types). Yield statements are subject to the same restrictions as return statements with respect to limited types. Restrictions on the placement of a yield statement are less restrictive than those for accept statements; a yield statement may occur in a subprogram (but the subprogram must occur within a generator body; the expected type/subtype for the yield statement comes from the nearest enclosing generator body). P_E occurs if a yield statement is executed by somebody who shouldn't (one way this corner-case situation can arise is if a task is declared inside of a generator body). Then we have the second form, type Positive_Generator yield Positive; which is sort of like a class-wide type (it is indefinite, and follows type conversion rules similar to the rules for converting between specific and class-wide tagged types). Such a type is characterized (completely?) by the subtype that it yields and its accessibility level. Such a type does not have a body. Type conversion between two generator types (of either sort - bodiless or not) requires statically matching subtypes, not just matching types. Incidentally, the accessibility level is why syntax like Positive'Generator was rejected. That wouldn't capture the accessibility level. The accessibility level is needed for, for example, for preventing dangling references in the case of a function which returns a generator. A client might look like function Next_With_Default (Gen : Positive_Generator) return Natural is begin if Gen'Yielding then return Gen'Next; else return 0; end if; end; We can flesh this proposal out if there is interest. What I view as the key ideas here are 1) two kinds of generator types: "concrete" and "interface-ish". 2) syntax for concrete generator types follows existing task/protected model. p.s. if you like any of the ideas in here, I probably got them from Raphael and Florian; the rest are mine. **************************************************************** From: Tucker Taft Sent: Wednesday, September 7, 2016 8:53 PM ... > 'Yielding is defined on these guys and means > "run until reaching either a yield statement or > the end of the generator body; return False if > and only if a yield statement is reached (the > yield statement is not executed in this case)." > In other words, 'Yielding indicates whether it is > ok to call Next. This seems backwards. Don't you mean return *True* if a yield statement is reached? > 'Terminated was considered instead of 'Yielding (albeit with the > opposite polarity), but it seemed odd that querying 'Terminated could > have a side effect. We have used phrases like "Has_Element" for iterators, so perhaps "Has_Next" might be used instead of "Yielding"? > A generator object executes/elaborates nothing until either 'Next or > 'Terminated is queried. Presumably you mean 'Yielding here. ... > Then we have the second form, > > type Positive_Generator yield Positive; It seems weird for the new reserved word "generator" not to appear somewhere here. Perhaps "generator interface Positive_Generator yield Positive;"? ... > Incidentally, the accessibility level is why syntax like > Positive'Generator > was rejected. That wouldn't capture the accessibility level. > The accessibility level is needed for, for example, for Three "for"s is at least one too many for this sentence! ;-) ... > p.s. if you like any of the ideas in here, I probably got them from > Raphael and Florian; the rest are mine. I'll blame you all equally... ;-) In any case, interesting! **************************************************************** From: Jeff Cousins Sent: Thursday, September 8, 2016 8:15 AM > One form is tied to a specific implementation (i.e., it has a body) and uses > syntax similar to the existing syntax for task types and protected types (but > with a new keyword). I don't think that generator can be a new keyword as it is already used by Ada.Numerics.Discrete_Random and Ada.Numerics.Float_Random. **************************************************************** From: Steve Baird Sent: Thursday, September 8, 2016 12:38 PM >> 'Yielding is defined on these guys and means >> "run until reaching either a yield statement or >> the end of the generator body; return False if >> and only if a yield statement is reached (the >> yield statement is not executed in this case)." >> In other words, 'Yielding indicates whether it is >> ok to call Next. > > This seems backwards. Don't you mean return *True* if a yield > statement is reached? Right. For a while I was using 'Terminated and I forgot to reverse the polarity here. >> 'Terminated was considered instead of 'Yielding (albeit with the >> opposite polarity), but it seemed odd that querying 'Terminated could >> have a side effect. > > We have used phrases like "Has_Element" for iterators, so perhaps > "Has_Next" might be used instead of "Yielding"? I like it. >> A generator object executes/elaborates nothing until either 'Next or >> 'Terminated is queried. > > Presumably you mean 'Yielding here. Right. Another case where I botched the late Terminated-to-Yielding transition. >> Then we have the second form, >> >> type Positive_Generator yield Positive; > > It seems weird for the new reserved word "generator" not to appear > somewhere here. > > Perhaps "generator interface Positive_Generator yield Positive;"? I agree, we'd like to see the word "generator" in there somewhere. I don't want to introduce generator interface types which are not interface types (analogous definitions have been a source of confusion in the past). If we can avoid that, then I like your syntax. >> Incidentally, the accessibility level is why syntax like >> Positive'Generator >> was rejected. That wouldn't capture the accessibility level. >> The accessibility level is needed for, for example, for > > Three "for"s is at least one too many for this sentence! ;-) One, two, three, for? The Positive'Generator approach has other problems as well. Are Positive'Generator and Natural'Generator two different types or not? Either choice leads to problems; pick your poison. And then there is the "unbounded number of types" problem with T'Generator, T'Generator'Generator, etc. Type-valued attributes ('Base, 'Class) are idempotent and want to keep it that way. **************************************************************** From: Tucker Taft Sent: Thursday, September 8, 2016 1:40 PM >> It seems weird for the new reserved word "generator" not to appear >> somewhere here. >> >> Perhaps "generator interface Positive_Generator yield Positive;"? >> > > I agree, we'd like to see the word "generator" in there somewhere. > > I don't want to introduce generator interface types which are not > interface types (analogous definitions have been a source of confusion > in the past). If we can avoid that, then I like your syntax. On the other hand, we could talk about "tagged interface" types vs. "generator interface" types, and not be too surprised that they follow different rules. A fundamental property of tagged interface types is that you essentially never see them without the "'Class" attribute, unless you are defining an abstract or null dispatching subprogram. But I don't see the need to use 'Class with these, since you really don't have a type hierarchy. On the other hand, that does bring up the question of a "generator interface" that yields a class-wide type. Would that be matched by a generator type that yields some specific type covered by the class-wide type? E.g., given: generator interface Expression_Gen yield Expression'Class; and type Primary is new Expression with ...; and generator type Primary_Gen(Tree : Expr_Tree) yield Primary; Would Primary_Gen(Blah) be acceptable for an Expression_Gen? An alternative here would be to define some kind of equivalence here between generator interfaces and tagged interfaces. We would need to define some (pseudo) dispatching operations corresponding to 'Next and 'Has_Next, and claim that a generator interface is equivalent to the 'Class type for a tagged interface, but that gets kind of heavy. It would probably be worth coding up several examples with various alternative syntaxes, to see how the feel. **************************************************************** From: Steve Baird Sent: Thursday, September 8, 2016 3:04 PM > On the other hand, we could talk about "tagged interface" types vs. > "generator interface" types, and not be too surprised that they follow > different rules. I was hoping to avoid making any changes in 3.9.4 (the section on interface types). I think this approach would involve a lot of (admittedly small) changes in that section. But I agree that the approach you describe is preferable to having "interface types" and "generator interface types" (where a generator interface type is not an interface type). > On the other hand, that does bring up the question of a "generator interface" > that yields a class-wide type. Would that be matched by a generator type that > yields some specific type covered by the class-wide type? Right, the rules for converting between generator types would need to be worked out. I expect the case you describe would be legal, but TBD. Generic formal generator types is a related area where some work would be needed. There are also questions about Pre and Post conditions and about separate subunits, just to name a couple. > An alternative here would be to define some kind of equivalence here between > generator interfaces and tagged interfaces. As an informal mental model, that seems like it might be useful. As a normative definition, I think it would probably lead to more problems than it is worth. > We would need to define some (pseudo) dispatching operations > corresponding to 'Next and 'Has_Next, and claim that a generator interface is > equivalent to the 'Class type for a tagged interface, but that gets kind of > heavy. Too heavy IMO. Thanks for the thoughtful feedback, **************************************************************** From: Raphael Amiard Sent: Friday, September 9, 2016 6:04 AM Great stuff Steve ! I like your syntax much better than the one I originally proposed so far. I think there are still some details to iron-out. > generator type Prime_Factory (Sieve_Size : Natural) yield Positive > with Post => Prime_Factory'Next'Result <= Sieve_Size; > > Then we have the second form, > > type Positive_Generator yield Positive; What is missing from your proposal is, how do you go from the first form to the second. So, I have this Positive_Generator type declared somewhere, and I have this client as above. Can I use an instance of the Prime_Factory type and pass it to next with default ? 1. If yes (which is what I would implicitly expect when reading your proposal), then from what I can see, you have some of the same problems that you'd have with the 'Generator approach: Is a generator type yielding a Natural compatible with the Positive_Generator type ? 2. If no, then you'd have to explicitly specify in the implementation that it is deriving from Positive_Generator, which breaks the modularity principle, and is annoying in practice: It means that you cannot use a positive yielding generator implemented by somebody that didn't know of your interface. Of course that can be worked around with conversion rules (as it is done for other types). You also have the "dummy type explosion" problem - Someday I'll count how many "access all String" access types we have in GPS, but probably more than 10 ! I guess my tongue-in-cheek question is, do you really want to wait for Ada 2030 to introduce anonymous generator types ? :) If Ada history is any indication, they end up being necessary every time. > The Positive'Generator approach has other problems as well. > Are Positive'Generator and Natural'Generator two different types or > not? Either choice leads to problems; pick your poison. And then there > is the "unbounded number of types" > problem with T'Generator, T'Generator'Generator, etc. > Type-valued attributes ('Base, 'Class) are idempotent and want to keep > it that way. I don't see how the "unbounded number of types" is a problem though. access access access String ? Is it because it's an attribute ? If that's the main differentiating problem, since your proposal is introducing a generator keyword, how about generator of Positive denoting the interface type ? I still don't really buy the type equivalence problems, because I think any approach will have to tackle them at some point, be it at the correspondence between interface and implementation types, or in the conversion rules. **************************************************************** From: Jeff Cousins Sent: Friday, September 9, 2016 6:09 AM As I said, the word generator is already in use for random numbers. **************************************************************** From: Tucker Taft Sent: Friday, September 9, 2016 8:26 AM > 1. If yes (which is what I would implicitly expect when reading your > proposal), then from what I can see, you have some of the same > problems that you'd have with the 'Generator approach: Is a generator > type yielding a Natural compatible with the Positive_Generator type ? > > 2. If no, then you'd have to explicitly specify in the implementation > that it is deriving from Positive_Generator, which breaks the > modularity principle, and is annoying in practice: I believe Steve was requiring only that the yielded subtypes match statically, which is a pretty well-defined requirement. But then we might want to relax that a bit to allow for classwide types, and perhaps unconstrained discriminated types. It turns out the matching rules required for "explicitly aliased" parameters might be just about right. See RM 6.4.1(6,6.1,6.2): "If the formal parameter is an explicitly aliased parameter, [...]. Further, if the formal parameter subtype F is untagged: 6.1/3 the subtype F shall statically match the nominal subtype of the actual object; or 6.2/3 the subtype F shall be unconstrained, discriminated in its full view, and unconstrained in any partial view." > ... It means that you > cannot use a positive yielding generator implemented by somebody that > didn't know of your interface. Of course that can be worked around > with conversion rules (as it is done for other types). You also have > the "dummy type explosion" problem - Someday I'll count how many > "access all String" access types we have in GPS, but probably more > than 10 ! I don't think we need to face these problems, if we use something close to 6.1/6.2 above for untagged subtype matching. **************************************************************** From: Tucker Taft Sent: Friday, September 9, 2016 8:52 AM > As I said, the word generator is already in use for random numbers. ... There is always a spoiler in every group... ;-) New reserved words are always a challenge. In a case-sensitive language, things aren't so bad if user identifiers generally start with an upper case letter, and reserved words are all in lower case. But alas, that isn't Ada. Note that "Yield" is the name of a procedure in Ada.Dispatching (D.2.1), but changing that seems like somewhat less disruptive. If we somehow use the combination of "task" and "yield" then we can get by with only one new reserved word. We could still use attributes (like 'Next and 'Has_Next) to take care of the remaining functionality. E.g.: task type Int_Gen(First, Last : Integer) yield Integer; task body Int_Gen yield Integer is begin for I in First .. Last loop yield I; end loop; end Int_Gen; R : Int_Gen(1, 10); ... while R'Has_Next loop J := R'Next; ... end loop; or for I in Int_Gen(3, 17) loop ... end loop; We could use an "abstract task type ... yield ..." as an interface-like thing: abstract task type Int_Generator yield Integer; procedure Foo(Generator : Int_Generator) is begin for I in Int_Generator loop ... end loop; end Foo; And we could use "task One_Shot yield Integer is ..." as a one-shot generator, that produces a single sequence over its lifetime: while One_Shot'Has_Next loop Z := One_Shot'Next; ... end loop; You could pass One_Shot to the above "Foo" procedure: Foo(One_Shot); or you could pass an instantiation of Int_Gen: Foo(Int_Gen(2,22)); or you could pass R: Foo(R); **************************************************************** From: Alan Burns Sent: Friday, September 9, 2016 9:26 AM But if you put task and yield together then, to many, the assumption will be that 'yield' means 'give up the processor' (allow pre-emption etc). Seems to me that a generator should generate! **************************************************************** From: Steve Baird Sent: Friday, September 9, 2016 1:24 PM > What is missing from your proposal is, how do you go from the first > form to the second. type conversion. > Is a generator > type yielding a Natural compatible with the Positive_Generator type ? No. See Tuck's reply (which is better than what I was about to write before I saw it). > I don't see how the "unbounded number of types" is a problem though. > access access access String ? Is it because it's an attribute ? This has been mentioned as an implementation problem for some compilers in the (distant) past. I agree that it is not a big deal, but I'd still prefer to avoid the 'Generator approach and go with explicitly declared "generator interface" types of some sort (for other reasons already described, notably accessibility). ---- > New reserved words are always a challenge. I agree, but I don't think the solution here is to somehow use the reserved word "task". Sure, you can view a generator as some sort of a passive task which only executes on somebody else's thread of control, but I don't think we want to emphasize that presentation in the RM. A generator task type which is not a task type seems as bad as a generator interface type which is not an interface type (worse because the meaning of "task" in Ada has been well established since 1983). So perhaps generator type Prime_Factory (Sieve_Size : Natural) yield Positive; becomes sire type Prime_Factory (Sieve_Size : Natural) beget Positive; . ---- > But if you put task and yield together then, to many, the assumption > will be that 'yield' means 'give up the processor' (allow pre-emption etc). Yes, but Raphael's first choice Yield_A_Value_While_Retaining_Control_Of_The_Processor seemed too verbose to me so I truncated it. More seriously, that does seem like another drawback of trying to present generators as some sort of task. **************************************************************** From: Tucker Taft Sent: Friday, September 9, 2016 1:41 PM >>> Then we have the second form, >>> >>> type Positive_Generator yield Positive; >> >> It seems weird for the new reserved word "generator" not to appear >> somewhere here. >> >> Perhaps "generator interface Positive_Generator yield Positive;"? >> > > I agree, we'd like to see the word "generator" in there somewhere. > > I don't want to introduce generator interface types which are not > interface types (analogous definitions have been a source of confusion > in the past). If we can avoid that, then I like your syntax. ... Perhaps instead of "interface" we could call these *abstract* generator types. An abstract generator type has no body, and is matched by an instance of a non-abstract generator type if the yielded subtypes match (for the appropriate definition of "match"). **************************************************************** From: Tucker Taft Sent: Friday, September 9, 2016 2:00 PM > As I said, the word generator is already in use for random numbers. ... --- > But if you put task and yield together then, to many, the assumption > will be that 'yield' means 'give up the processor' (allow pre-emption etc). > > Seems to me that a generator should generate! ... I can feel the term "coroutine" coming on. Raphael originally wanted coroutines; perhaps our search for an appropriate reserved word will bring us back to that. [abstract] COROUTINE [type] identifier [discriminant_part] YIELD subtype_mark; COROUTINE body identifier YIELD subtype_mark is -- I think "YIELD" part should re-appear on the body ... BEGIN ... YIELD expression; ... END identifier; There might be some additional functionality provided if you have two coroutines talking with one another, but for simple use, it would have the same functionality we proposed for generators. **************************************************************** From: Steve Baird Sent: Friday, September 9, 2016 2:11 PM > Perhaps instead of "interface" we could call these *abstract* > generator types. I like it. I'd have to think about whether an abstract generator type would be an abstract type, but it is certainly (definitely?) indefinite so it is pretty close in any case. **************************************************************** From: Raphael Amiard Sent: Friday, September 9, 2016 2:17 PM >>Perhaps instead of "interface" we could call these *abstract* generator >>types. > >I like it. > >I'd have to think about whether an abstract generator type >would be an abstract type, but it is certainly (definitely?) >indefinite so it is pretty close in any case. I like it too ! I was thinking about "dispatching generator", because after all that's the important distinction for the user, but abstract sounds good. **************************************************************** From: Steve Baird Sent: Friday, September 9, 2016 2:17 PM > I can feel the term "coroutine" coming on. But isn't "coroutine" a more general term than what we want? That is, every generator is a coroutine but not every coroutine is a generator? But I agree it is worth considering, especially if you don't like my "sire" types which "beget" values. Oh well, back to the scrabble bag. **************************************************************** From: Tucker Taft Sent: Friday, September 9, 2016 2:31 PM >> I can feel the term "coroutine" coming on. > > But isn't "coroutine" a more general term than what we want? That is, > every generator is a coroutine but not every coroutine is a generator? Yes, that is why I alluded to some additional functionality which might exist when two such coroutines are interacting. If we ultimately think we might have both, then we might want to use the term "coroutine" for both concepts, but with a coroutine designed primarily as a generator having some limitations, at least when called from a non-coroutine. > But I agree it is worth considering, especially if you don't like my > "sire" types which "beget" > values. Oh well, back to the scrabble bag. Right... **************************************************************** From: Tullio Vardanega Sent: Friday, September 9, 2016 2:30 PM >> I can feel the term "coroutine" coming on. > > But isn't "coroutine" a more general term than what we want? That is, > every generator is a coroutine but not every coroutine is a generator? Yes, indeed. That sort of correspondence is certainly not bijective, which suggests that using the term "coroutine" we would expand beyond the intent. **************************************************************** From: Jean-Pierre Rosen Sent: Sunday, September 11, 2016 2:07 AM Here is the generator, written using a task: with Text_IO; use Text_IO; procedure Test_Gen is task type Prime_Factory (Sieve_Size : Natural) is entry Next (Yield : out Positive) with Post => Yield <= Sieve_Size; end Prime_Factory; task body Prime_Factory is Is_Composite : array (2 .. Sieve_Size) of Boolean := (others => False); Current : Integer range Is_Composite'Range := 2; procedure Mark_Multiples (Prime : Positive) is Multiple : Positive := Prime; begin while Multiple <= Sieve_Size - Prime loop Multiple := Multiple + Prime; Is_Composite (Multiple) := True; end loop; end Mark_Multiples; begin while Current <= Sieve_Size loop if not Is_Composite (Current) then Mark_Multiples (Prime => Current); accept Next ( Yield : out Positive) do Yield := Current; end Next; end if; Current := Current + 1; end loop; end Prime_Factory; My_Gen : Prime_Factory (100); Prime : Positive; begin while My_Gen'Callable loop My_Gen.Next (Prime); Put_Line (Positive'image(Prime)); end loop; end Test_Gen; 1) The code is almost identical to the generator proposal 2) The only significant difference is that the generator is a function; function entries could be added to the language, which would be a welcomed addition, independently of the generator proposal 3) As written, the generator runs concurrently with the consumer. This could be considered a benefit of this solution. IF sequential behaviour is required, or IF there are fears about scheduling costs (but a generator will need some kind of context switching anyway), THEN the notion of passive tasks can be introduced. This notion can be a useful addition, independently of generators 4) Generator interfaces come at no cost (we already have task interfaces) 5) 'Next is simply an entry call. 'Yielding is simply 'Callable. Admitedly, there is a small race condition in the concurrent case, but I don't think it is a big deal at this point. In the passive task case, it is sufficient that evaluating 'Callable forces a "run until block or complete" on the target task. Note that 'Yielding on a generator will need to do the same anyway. -- Honestly, I don't see the value of adding a whole load of syntax and complicated stuff for something that we can already do (and could already do in Ada 83!). Remember, Ada is about the "building blocks approach". We do have the main building blocks, some small blocks can be added (and could serve other purposes, which is the landmark of good building blocks). And don't forget that adding features not only complicates the compiler, it also makes teaching and promoting the language more difficult. Python people are very excited about generators, because they don't have high level tasking like Ada (only basic threads and synchronization, nothing close to the rendezvous AFAIK). I see no benefit in copying other languages workarounds for features that they miss and that we have. Hmmm... Where did I put that asbestos suit? **************************************************************** From: Erhard Ploedereder Sent: Sunday, September 11, 2016 5:27 AM Lots of folks could immediately grasp the coroutine idea, which is why I like it (including the YIELD). Syntactic Suggestion: no need for a keyword. [abstract] FUNCTION [type] identifier [discriminant_part] YIELD subtype_mark; would do just fine. The YIELD vs RETURN tells the difference. **************************************************************** From: Tucker Taft Sent: Sunday, September 11, 2016 8:36 AM It is a little weird to have both a "function type" and a "type is access function" but I agree that using the word "Yield" could be adequate to identify these as generators. The instances of such a "function type" are initialized generator objects that have a 'Next and a 'Has_Next attribute, whereas the "instances" of an access-function type are pointers to (as yet uncalled) functions. If you omit the "type" then you sort of have to omit the parameters as well, because these become singletons that represent initialized generator objects, so there is no way to further parameterize them. There are some other weirdnesses -- the parameter passing semantics are somewhat different (more like discriminants than parameters), and the originally proposed syntax omitted the parameter list from the body and instead had "body" explicitly. Presumably if we use "function" we would repeat the parameter list (including the "yield") and omit the "body" so it would look like a "normal" function body except for the "yield" instead of "return." I guess these begin to feel like pretty different beasts! **************************************************************** From: Erhard Ploedereder Sent: Sunday, September 11, 2016 2:59 PM > Presumably if we use "function" we would repeat the parameter list > (including the "yield") yes. > and omit the "body" so it would look like a "normal" function body > except for the "yield" instead of "return." yes. The point being that this is a coroutine in all respects. "returning" (including running out of code) ends the generator/iterator, "yielding" continues it. Users would not have to worry about one or the other, no need for a racy "hasNext" or suchlike. Presumably, rather than "type" in the signature, one would write a generic coroutine instead. One less concept to worry about. **************************************************************** From: Jeff Cousins Sent: Monday, September 12, 2016 9:02 AM Hi. I've done a bit of research on some suggested new keywords. Generator is already used by Ada.Numerics.Discrete_Random and Ada.Numerics.Float_Random. Yield is already used by Ada.Dispatching. Parallel isn't already used by the language, so I searched through about a million lines of our source code. There was one enumeration type with literals such as Parallel, Orthogonal, ..., used in 3 places. I'm sure that we could live with changing them. But new keywords aren't something to be introduced lightly. The Ada 2005 new keywords had quite a bad impact on us. I suspect many companies would have stuck with Ada 95 until the code could be replaced by C++. **************************************************************** From: Bob Duff Sent: Monday, September 12, 2016 9:16 AM > But new keywords aren't something to be introduced lightly. I agree. Time to fight the "unreserved keyword" battle again? **************************************************************** From: Raphael Amiard Sent: Monday, September 12, 2016 10:07 AM > But new keywords aren't something to be introduced lightly. The Ada > 2005 new keywords had quite a bad impact on us. I suspect many > companies would have stuck with Ada 95 until the code could be > replaced by C++. Out of curiosity, would this impact have been reduced by an automatic migration tool ? This is what Apple is doing with Swift when they do backward-incompatible releases. Furthermore, we could provide some degree of insurance that the code is conform to the old version. **************************************************************** From: Jeff Cousins Sent: Monday, September 12, 2016 10:21 AM The mechanics of changing the code weren’t a big problem, it was more a management problem specific to the word “interface”. Within our naval division there was a convention of defining the interface to a package in a .interface child package (and the implementation in a .impl child package), and where this interface formed the interface between code from one site and code from another site, the changes to avoid using the keyword had to be synchronised across sites. **************************************************************** From: Steve Baird Sent: Monday, September 12, 2016 6:56 PM > 2) The only significant difference is that the generator is a > function; function entries could be added to the language, which would > be a welcomed addition, independently of the generator proposal One important (IMO) part of the generator proposal is allowing yield statements in subprograms nested within the generator. One can, for example, traverse a recursive data structure using a recursive subprogram, yielding values along the way. This was mentioned in the proposal but not in the example. To provide this functionality using passive tasks, we'd have to be willing to relax the current restrictions on accept statement placement. There are also implementation issues associated with storage management and accessibility, but these may be pretty much the same with either approach. For example, if the generator-or-passive-task-or-whatever yields an indefinite subtype, then the caller may have to pass in a storage pool under the covers. I remember that the small-integer implementation model for runtime accessibility checking (which is already broken for other reasons) relied on not having to deal with entry functions. > 3) As written, the generator runs concurrently with the consumer. This > could be considered a benefit of this solution. IF sequential > behaviour is required, or IF there are fears about scheduling costs > (but a generator will need some kind of context switching anyway), > THEN the notion of passive tasks can be introduced. This notion can be > a useful addition, independently of generators. These guys are not intended to introduce another mechanism for concurrent execution. So I'd say, yes, sequential behaviour is required. Generators (at least as I envision them) don't even have the mutual exclusion guarantee of a protected record. They are like the iterators for the predefined container packages in that respect; if you want mutual exclusion, you have to add that yourself. If you or someone else would like to write up a "passive task" proposal, we could certainly consider it as an alternative to generators. My guess is that the other issues described in this message (indefinite result subtypes, accept statement placement restrictions) would be problematic, but that's just a guess. > Python people are very excited about generators, because they don't > have high level tasking like Ada (only basic threads and > synchronization, nothing close to the rendezvous AFAIK). I see no > benefit in copying other languages workarounds for features that they miss and > that we have. That's similar to the reaction that I had when I first heard about protected records. Why do we need these guys if we have tasks? I've since changed my mind on that one. **************************************************************** From: Raphael Amiard Sent: Tuesday, September 13, 2016 5:33 AM >> 2) The only significant difference is that the generator is a function; >> function entries could be added to the language, which would be a >> welcomed addition, independently of the generator proposal > > One important (IMO) part of the generator proposal is allowing yield > statements in subprograms nested within the generator. One can, for > example, traverse a recursive data structure using a recursive > subprogram, yielding values along the way. This was mentioned in > the proposal but not in the example. To provide this functionality > using passive tasks, we'd have to be willing to relax the current > restrictions on accept statement placement. I agree that this is important. >> 3) As written, the generator runs concurrently with the consumer. This >> could be considered a benefit of this solution. IF sequential behaviour >> is required, or IF there are fears about scheduling costs (but a >> generator will need some kind of context switching anyway), THEN the >> notion of passive tasks can be introduced. This notion can be a useful >> addition, independently of generators. > > These guys are not intended to introduce another mechanism for > concurrent execution. So I'd say, yes, sequential behaviour is > required. > > Generators (at least as I envision them) don't even have the mutual > exclusion guarantee of a protected record. They are like the iterators > for the predefined container packages in that respect; if you want > mutual exclusion, you have to add that yourself. Having task safe behavior for generators would incur a performance penalty in single-task use cases, which will be the majority IMHO, so not a good thing. > If you or someone else would like to write up a "passive task" > proposal, we could certainly consider it as an alternative to > generators. My guess is that the other issues described in this > message (indefinite result subtypes, accept statement placement > restrictions) would be problematic, but that's just a guess. I would like the people who spoke up against passive tasks at the meeting (Tucker and Erhard come to mind) to contribute to this discussion. The only way I can sum up the argument against them right now is "If it looks like a Task, I'll expect it to behave like a task (regarding synchronization, and other properties), which it won't in this case. Personally, I have no strong preference for either option, certainly not enough to make a counter-proposal at this stage. I care about having the desired semantics, to express lazy iterators that can be used easily, for example, but that seems achievable following both proposals at the moment. One thing that *could* make me prefer the "separate construct" proposal, is if we decide that passive tasks needs to be synchronization safe, like protected objects. That will incur a performance penalty in single-threaded cases which I'd rather avoid. >> Python people are very excited about generators, because they don't have >> high level tasking like Ada (only basic threads and synchronization, >> nothing close to the rendezvous AFAIK). I see no benefit in copying >> other languages workarounds for features that they miss and that we have. > > That's similar to the reaction that I had when I first heard about > protected records. Why do we need these guys if we > have tasks? I've since changed my mind on that one. Python people are not really excited about generators, they consider them a given, it has been in the language since a very long time :) Also, I think you're making the mistake of considering the two constructs to have the same goals. Python users *do* miss something like Ada tasks, but that's not what they use generators for. That doesn't kill the idea of passive tasks of course, but it puts it in perspective: It would need to satisfy the use cases generators are actually used for (lazy sequences for example). The sieve example that you converted to tasking has the advantage of concurrent execution, but it's also a drawback: - You will have much more overhead spawning the task, which in some cases will make the approach counter productive - You will make any correctness analysis of the produced code much harder - You will make it unusable in contexts where tasks/threads are disallowed. This would be solved by passive tasks, which is why I'm not against them. **************************************************************** From: Jean-Pierre Rosen Sent: Wednesday, September 14, 2016 6:21 AM >> 2) The only significant difference is that the generator is a >> function; function entries could be added to the language, which >> would be a welcomed addition, independently of the generator proposal > > One important (IMO) part of the generator proposal is allowing yield > statements in subprograms nested within the generator. One can, for > example, traverse a recursive data structure using a recursive > subprogram, yielding values along the way. This was mentioned in the > proposal but not in the example. To provide this functionality using > passive tasks, we'd have to be willing to relax the current > restrictions on accept statement placement. The restriction on accept statements in tasks is, AFAIK, due to making sure that a task accepts only its own entries. If generators allow any inner declaration (as they should), then you can declare a generator inside a generator, and you'll have the same problem to make sure that a procedure yields only on behalf of the right generator. [...] >> 3) As written, the generator runs concurrently with the consumer. >> This could be considered a benefit of this solution. IF sequential >> behaviour is required, or IF there are fears about scheduling costs >> (but a generator will need some kind of context switching anyway), >> THEN the notion of passive tasks can be introduced. This notion can >> be a useful addition, independently of generators. > > These guys are not intended to introduce another mechanism for > concurrent execution. So I'd say, yes, sequential behaviour is > required. They are not /intended/, but allowing them to run concurrently is a nice plus. It allows the generator to anticipate on the next value. > Generators (at least as I envision them) don't even have the mutual > exclusion guarantee of a protected record. They are like the iterators > for the predefined container packages in that respect; if you want > mutual exclusion, you have to add that yourself. > > If you or someone else would like to write up a "passive task" > proposal, we could certainly consider it as an alternative to > generators. My guess is that the other issues described in this > message (indefinite result subtypes, accept statement placement > restrictions) would be problematic, but that's just a guess. Actually, it's not exactly a "passive task" for generators proposal. I argue that Ada already has the necessary building blocks to provide the fundamental functionality of generators: providing values when needed, without constructing the whole set. I view passive tasks (as well as function entries) as independent improvements, that could be useful for generators as well as other use cases. Moreover, the more I think about it, the more I think that generators will have to deal with exactly the same issues as tasks. Which is not surprising: after all, they ARE independent threads of control that maintain a state independently from the callers. >> Python people are very excited about generators, because they don't >> have high level tasking like Ada (only basic threads and >> synchronization, nothing close to the rendezvous AFAIK). I see no >> benefit in copying other languages workarounds for features that they miss >> and that we have. > > That's similar to the reaction that I had when I first heard about > protected records. Why do we need these guys if we have tasks? I've > since changed my mind on that one. I understand that position, but it is a matter of ROI between the cost of adding this to the language and the benefits. From the previous discussions, I fear the cost is high, it's somehow duplicating what has been done with tasks, with low benefit. **************************************************************** From: Jean-Pierre Rosen Sent: Wednesday, September 14, 2016 6:31 AM > Having task safe behavior for generators would incur a performance > penalty in single-task use cases, which will be the majority IMHO, so > not a good thing. I don't think that it would require more than global lock, IF we want it to be task safe (for passive tasks, active ones are inherently task safe). >> If you or someone else would like to write up a "passive task" > proposal, we could certainly consider it as an alternative to > generators. My guess is that the other issues described in this > message (indefinite result subtypes, accept statement placement > restrictions) would be problematic, but that's just a guess. Maybe, but I would be surprised if the same problems don't arise with iterators. > Python people are not really excited about generators, they consider > them a given, it has been in the language since a very long time :) > > Also, I think you're making the mistake of considering the two > constructs to have the same goals. Python users *do* miss something > like Ada tasks, but that's not what they use generators for. My remark was the other way round: generators are easily constructed with tasks. If you need generators without tasks, you need a special construct. > That doesn't kill the idea of passive tasks of course, but it puts it > in > perspective: It would need to satisfy the use cases generators are > actually used for (lazy sequences for example). The sieve example that > you converted to tasking has the advantage of concurrent execution, > but it's also a drawback: > > - You will have much more overhead spawning the task, which in some > cases will make the approach counter productive I learned to be careful when talking about efficiency without actual measures... A generator will also need its own context, its own stack... > - You will make any correctness analysis of the produced code much > harder > - You will make it unusable in contexts where tasks/threads are > disallowed. > > This would be solved by passive tasks, which is why I'm not against > them. Right **************************************************************** From: Erhard Ploedereder Sent: Thursday, September 15, 2016 4:42 AM To me, the question whether "yield" is tied to the immediately enclosing construct is a primary issue, based on which the language concepts will differ considerably. (A "yield" anywhere in a nesting of subprogram calls is a troublesome notion much like an "accept" anywhere, which was disallowed for that reason.) In the absence of a nesting requirement, the coroutine principle is simpler than a tasking model because it is a strictly sequential construct vis-a-vis its caller and a lot less cumbersome than a "has-more"/"get-next" setup. As to parallel use, I am on the fence. But, if containers are not task safe, I see no reason to treat generators differently. **************************************************************** From: Tucker Taft Sent: Thursday, September 15, 2016 12:18 PM I wonder whether an alternative approach might be to provide a simple type like Go's "channel," effectively a queue or pipe, which might or might not provide any buffering. There would be an operation to put things into the channel, and an operation to get things out of the channel, and an ability to put in an end-of-channel indicator, and an ability to detect the end-of-channel indicator. The special thing about such a channel is that when a caller tries to put into a full channel, or get from an empty channel, it is suspended and the thread/coroutine suspended waiting on the "other end" is awakened. If there is nothing suspended on the other end, then the caller gets an indication that the channel is finished, which it could treat as an error or a normal termination indication. There could be syntactic sugar to make this all pleasant to use. The main point is that you could have multiple channels associated with a single coroutine, so you could easily write various kinds of multiplexors (splitters, junctions, etc.) which combine channels in interesting ways. The idea is to separate the channel from the coroutine, rather than linking them tightly. At this point a coroutine becomes very nearly a passive task, and syntactic sugar could be used to create special cases like generators (one-to-one connection between a channel and a coroutine), but we would have a common underlying semantics. You could imagine having synchronized channels which could be used with "real" tasks, and unsynchronized, single-threaded channels, for use with coroutine/passive tasks. Even Ada's task entries could be described using this channel model, with each entry represented by a channel going into the task, and a return channel if there are any output parameters. One of the main things I don't like about the classic coroutine model is that coroutines need to name one another to pass control back and forth. Generators are much friendlier in that the generator doesn't need to know the name of the thread requesting the data. The channel model moves further away from tasks having to know each other's name. All they need is access to an open channel and they can generate or receive values. Some examples are clearly needed to evaluate this. I'll try to create some over the next few days... *************************************************************** From: Tucker Taft Sent: Thursday, September 15, 2016 12:29 PM One nice feature of this is that it finesses the issue of nested yields/accepts/etc. Since the channel is an object, you can pass it around as needed, including across recursive calls. If it is an "unsynchronized" channel, then you don't want to pass it to a separate (active) task, but other than that, you could pass it anywhere you want, and use it how you see fit. Obviously an appropriate channel should be usable with the new Ada 2012 iterator syntax, so you can "drain" a channel using a "for X of Channel" loop. But you could also explicitly Get items out of the channel. Now that we have the aggregate that has a "for" inside it, e.g. "(for I in 1 .. 10 => I**2)" aka "iterated component association," perhaps we could also "fill" a channel using something like: Channel := (for I in 1..10 => I**2); or My_Channel : Channel_Type is (for I in 1..10 => I**2); Isn't language design fun? **************************************************************** From: Steve Baird Sent: Thursday, September 15, 2016 12:49 PM > To me, the question whether "yield" is tied to the immediately > enclosing construct is a primary issue, based on which the language > concepts will differ considerably. (A "yield" anywhere in a nesting of > subprogram calls is a troublesome notion much like an "accept" > anywhere, which was disallowed for that reason.) I think a) the issue is important b) yield statements in nested subprograms need to work (e.g., inside a subprogram which is passed to some container's iterator routine via an access-to-subprogram parameter) c) we need runtime checks to handle the case where the yield statement is executed in the wrong context; we don't want this to be erroneous d) those runtime checks will be as costly (in both complexity and performance) as the analogous checks would be if we decided to allow accept statements inside of a subprogram declared inside of the corresponding task body. For example, an implementation could save the current task_id in a variable declared at generator body level when a generator starts executing (i.e., whenever 'Next or 'Has_Next is called) and check that it matches the current task when a yield statement is executed. [The generator could also set the variable to null when 'Next or 'Has_Text completes and check that the variable is null when 'Next or 'Has_Next are called. This would detect attempts to have two 'Next/'Has_Next calls in progress at once, at least in the sequential case (the race condition case could also be handled, depending on the details of how this is implemented). So we might get additional benefits out of this mechanism beside allowing nested-subprogram yield statements.] For a task body the task_id variable could be a constant, initialized during task body elaboration, and checked when an accept statement inside a subprogram is executed. Before deciding to support this, we'd need to decide whether we are really doing users a favor by introducing another construct which depends for correctness on being executed by a particular task. We already have this situation with, for example, most calls to Current_Task (in particular, most clients of Ada.Task_Attributes). I think the benefits of supporting nested-subprogram yield statements outweigh the costs, but this issue is (IMO) one of the costs. ... > I wonder whether an alternative approach might be to provide a simple > type like Go's "channel, ... > One nice feature of this is that it finesses the issue of nested > yields/accepts/etc Tuck - That does sound appealing. I look forward to seeing your example. **************************************************************** From: Brad Moore Sent: Friday, September 16, 2016 10:05 AM > I understand that position, but it is a matter of ROI between the cost > of adding this to the language and the benefits. From the previous > discussions, I fear the cost is high, it's somehow duplicating what > has been done with tasks, with low benefit. I have similar concerns that the language already has ways to do this sort of thing with similar ease of use. I see this as a typical producer/consumer problem. Consider a buffer object as a "generator", where the buffer blocks on reading if the buffer is empty, and blocks on writing if the buffer is full. A buffer could be sized to hold a small number of objects, or even a single object. The buffer might even be a streamable object. I have several such buffer types in the dequesterity buffer project, for example. http://dequesterity.sourceforge.net eg. See the Stream_Buffers.Ravenscar_Bounded package for a streamable buffer that supports the above blocking semantics; The client of the "generator" buffer calls 'Read whenever it needs another value. The producer is the generator implementation that is a procedure called from a dedicated task that calls 'write to push successive values into the generator as they are needed. The generator implementation could be generisized for ease of use so that the task is hidden, and the client code could just be a procedure that is passed an access to the the generator buffer, and simply is a loop that writes values to the buffer. It strikes me that this achieves a similar effect as the generator idea being proposed, without adding more complexity to the language, and yet providing a similar ease of use. As a stream object, there is a fair amount of flexibility, for producing things like indefinite types, and for class wide object factories, etc. **************************************************************** From: Raphael Amiard Sent: Friday, September 16, 2016 11:06 AM > It strikes me that this achieves a similar effect as the generator > idea being proposed, without adding more complexity to the language, > and yet providing a similar ease of use. I disagree about the latest part (about ease of use). If I understand you correctly, you only talk about the external semantics of the generator (the aspect were it provides a stream of objects). You can achieve a similar effect with an iterator object (just an object with a Next). Where generators shine is expressing the logic of your iterator, allowing you not to have any state to maintain between iterations - which, as Steve outlined, gets particularly interesting when that state is a stack of recursive calls. We have such an iterator in Libadalang by the way, look at https://github.com/AdaCore/langkit/blob/master/langkit/support/langkit_support-tree_traversal_iterator.adb#L7 This is the kind of code that generators are meant to simplify. Indeed, this is just a few lines of code (and no type declaration and all) with generators. If you are talking about using tasks feeding a buffer, this could indeed work, and would provide similar expressivity, but is extremely heavy-weight in terms of run-time. I do not want to spawn a task every time I want to find something in a tree - or, for that matter, have a long running task for that purpose. **************************************************************** From: Randy Brukardt Sent: Friday, September 16, 2016 11:37 AM I agree with Brad, and also have implementation concerns for existing compilers. **************************************************************** From: Jean-Pierre Rosen Sent: Friday, September 16, 2016 2:50 PM > If you are talking about using tasks feeding a buffer, this could > indeed work, and would provide similar expressivity, but is extremely > heavy-weight in terms of run-time. I do not want to spawn a task every > time I want to find something in a tree - or, for that matter, have a > long running task for that purpose. I'd like to have some data about that "extremely heavy weight". Are you talking about memory space, efficiency? And are you sure that generators would be significantly lighter? A generator will need a context switch much similar to a task switch. **************************************************************** From: Brad Moore Sent: Saturday, September 17, 2016 12:44 AM >> It strikes me that this achieves a similar effect as the generator >> idea being proposed, without adding more complexity to the language, >> and yet providing a similar ease of use. > > I disagree about the latest part (about ease of use). If I understand > you correctly, you only talk about the external semantics of the > generator (the aspect were it provides a stream of objects). You can > achieve a similar effect with an iterator object (just an object with > a Next). > > Where generators shine is expressing the logic of your iterator, > allowing you not to have any state to maintain between iterations - > which, as Steve outlined, gets particularly interesting when that > state is a stack of recursive calls. I see no difference, since the task has its own stack, there is no state that needs to be saved, and recursive calls work fine. To illustrate, I implemented a generator that iterates through a binary tree of nodes. Here is the client code with both the generator implementation, and the client usage. with Integer_Tree; with Generators; with Ada.Text_IO; use Ada.Text_IO; procedure Test_Generators is Tree : constant Integer_Tree.Tree := Integer_Tree.Create; use type Integer_Tree.Node_Access; -- Implementation of the generator. Note this is a recursive -- call. Since the 'Write is blocking, the state of the stack -- saved until the next value is read by the client. procedure Tree_Iterate (Gen : Generators.Generator) is procedure Next (Root : Integer_Tree.Tree) is begin if Root.Left /= null then Next (Root.Left.all); end if; Integer'Write (Gen, Root.Value); if Root.Right /= null then Next (Root.Right.all); end if; end Next; begin Next (Tree); end Tree_Iterate; -- Instantiating the generator using the implementation above package My_Generator is new Generators.Implementation (Processing => Tree_Iterate); Gen : constant Generators.Generator := My_Generator.Create; Value : Integer; begin -- The client Code that reads values out of the generator while not My_Generator.Done loop Value := Integer'Input (Gen); Put_Line ("Value is" & Integer'Image (Value)); end loop; end Test_Generators; How much of a difference would there be to code the example above using the proposed generator syntax? I suspect there wouldn't be significant difference in terms of ease of expression. To see my reusable Generator generic, it is as follows. with Stream_Buffers; use Stream_Buffers; package Generators is type Generator is access all Streamable_Buffer'Class; generic with procedure Processing (Gen : Generator); package Implementation is function Create return Generator; function Done return Boolean; end Implementation; end Generators; with Stream_Buffers.Ravenscar_Bounded; package body Generators is package body Implementation is Still_Processing : Boolean := True; Bounded_Ravenscar_Buffer : aliased Stream_Buffers.Ravenscar_Bounded.Ravenscar_Buffer.Buffer (Maximum_Capacity => 100); Bounded_Stream_Store : aliased Stream_Buffers.Ravenscar_Bounded.Buffer (Data => Bounded_Ravenscar_Buffer'Access); function Create return Generator is begin return Bounded_Stream_Store'Unchecked_Access; end Create; task Generator_Implementation is end Generator_Implementation; task body Generator_Implementation is begin Processing (Bounded_Stream_Store'Unchecked_Access); Still_Processing := False; end Generator_Implementation; function Done return Boolean is begin return not Still_Processing; end Done; end Implementation; end Generators; Also, the Tree package in case anyone wants to build the example, and try it out.... package Integer_Tree is type Node; type Node_Access is access Node; type Node is record Value : Integer; Left, Right : Node_Access := null; end record; subtype Tree is Node; function Create return Tree; end Integer_Tree; with Ada.Numerics.Discrete_Random; use Ada.Numerics; package body Integer_Tree is package Random_Integers is new Discrete_Random (Result_Subtype => Integer); procedure Insert (New_Node : Node_Access; Root : in out Tree); function Create return Tree is Result : Node; Gen : Random_Integers.Generator; begin Result.Value := Random_Integers.Random (Gen); for I in 1 .. 100 loop Insert (New_Node => new Node'(Value => Random_Integers.Random (Gen), Left => null, Right => null), Root => Result); end loop; return Result; end Create; procedure Insert (New_Node : Node_Access; Root : in out Tree) is begin if New_Node.Value < Root.Value then if Root.Left = null then Root.Left := New_Node; return; else Insert (New_Node, Root.Left.all); end if; elsif New_Node.Value = Root.Value then return; elsif New_Node.Value > Root.Value then if Root.Right = null then Root.Right := New_Node; else Insert (New_Node, Root.Right.all); end if; end if; end Insert; end Integer_Tree; For the Stream_Buffers packages, that can be found at dequesterity.sourceforge.net > We have such an iterator in Libadalang by the way, look at > https://github.com/AdaCore/langkit/blob/master/langkit/support/langkit > _support-tree_traversal_iterator.adb#L7 > > > This is the kind of code that generators are meant to simplify. > Indeed, this is just a few lines of code (and no type declaration and > all) with generators. > > If you are talking about using tasks feeding a buffer, this could > indeed work, and would provide similar expressivity, but is extremely > heavy-weight in terms of run-time. I do not want to spawn a task every > time I want to find something in a tree - or, for that matter, have a > long running task for that purpose. It strikes me that this buffer implementation might actually be more efficient than the generator approach. With the generator syntax, my understanding is that a stack context switch needs to occur back and forth every time another value is read. With the buffer approach, the task typically has the next values to be read already sitting in the buffer, and to read the buffer, there is no context switch needed. The task in the generator object above automatically exits when the iteration if complete, but other schemes could be devised to terminate the task when it is no longer needed. **************************************************************** From: Erhard Ploedereder Sent: Monday, September 26, 2016 6:04 PM > One nice feature of this is that it finesses the issue of nested > yields/accepts/etc. Since the channel is an object, you can pass it > around as needed, including across recursive calls. If it is an > "unsynchronized" channel, then you don't want to pass it to a separate > (active) task, but other than that, you could pass it anywhere you > want, and use it how you see fit. It ought to be a limited object. In some channel models, passing the channel implies closing/terminating the channel for the passer. This also finesses the parallel access, since passing the channel across threads is a synchronizing event, so that at any time only one thread can feed off the channel, resp. put into the channel. (I like channels.) **************************************************************** From: Florian Schanda Sent: Wednesday, September 28, 2016 5:20 AM > > I can feel the term "coroutine" coming on. > > But isn't "coroutine" a more general term than what we want? That is, > every generator is a coroutine but not every coroutine is a generator? It is, but its much clearer than anything relating "tasks". Ada already has this problem of having curious names for something everyone else has a different name (hello tagged types). Lets *not* make this worse. Task means there is some parallel processing going on and that is the emphasis. It also makes you think about locking, scheduling and waiting. This is *not* what a generator is about. It is educational on some level to think about these as tasks, but I don't think the purpose of the Ada language is to educate people who didn't do this stuff at University. :) How about "limited coroutine" or "semicoroutine". I know limited has a very different meaning in ada, but "limited coroutine" really describes quite well what a generator is: its a co-routine but with some limitations. It would also allow us later to add coroutines ;) **************************************************************** From: Brad Moore Sent: Wednesday, September 28, 2016 9:10 AM >>> I can feel the term "coroutine" coming on. >> >> But isn't "coroutine" a more general term than what we want? That is, >> every generator is a coroutine but not every coroutine is a >> generator? > > It is, but its much clearer than anything relating "tasks". > > Ada already has this problem of having curious names for > something everyone else has a different name (hello tagged types). > Lets *not* make this worse. But for the generator library abstraction I presented, the use of a task is an implementation detail. Users of the abstraction do not need to be aware that a task is involved. One could in theory implement the abstraction using something lighter weight than tasks if there is some benefit to doing so. I'm concerned about making the complexity of the language syntax worse when a similar capability can be provided using existing syntax. The argument that other languages had to create special gizmos because they don't have tasks, doesn't seem applicable to Ada. I think the concept of a generator is a useful abstraction, and could be worth standardizing in some form. I have not seen any convincing arguments about why this couldn't just be a library abstraction however. **************************************************************** From: Tucker Taft Sent: Wednesday, September 28, 2016 9:20 AM >> One nice feature of this is that it finesses the issue of nested >> yields/accepts/etc. Since the channel is an object, you can pass it >> around as needed, including across recursive calls. If it is an >> "unsynchronized" channel, then you don't want to pass it to a >> separate >> (active) task, but other than that, you could pass it anywhere you >> want, and use it how you see fit. > > It ought to be a limited object. For sure. > In some channel models, passing the channel implies > closing/terminating the channel for the passer. This also finesses the > parallel access, since passing the channel across threads is a > synchronizing event, so that at any time only one thread can feed off > the channel, resp. put into the channel. I have seen this called the "hand-off" model of parameter passing. The language Hermes used that (as does ParaSail, and effectively SPARK as well). Essentially if you give another entity a writable handle to something, you have no access to it until the other entity relinquishes that handle. > (I like channels.) Good to hear. **************************************************************** From: Raphael Amiard Sent: Monday, October 3, 2016 1:53 PM > But for the generator library abstraction I presented, the use of a > task is an implementation detail. It is not an implementation detail I think: 1. If you access any outer variable that is not part of the task body, you'll have potential race conditions. If you access synchronized objects you'll have potential deadlocks, etc.. You have all the problems of task based programming. 2. Even for the use of the synchronization buffer, you'll have synchronization involved, which means overhead, but also a potential system call on some systems, which can be a very bad thing if you're calling that in a tight (soft-realtime) loop. 3. Determinism. You control the order of execution of your generator. It doesn't matter in simple examples, but is a big big plus of generators in the real world. 4. Those simpler characteristics also mean that the resulting feature will be *much* easier to use in some embedded footprints. Determinism + reduced runtime support means that it's much easier to certify code using generators than to certify code using tasks. It also means that having support in ZFP/SFP runtimes will also be much easier to implement. **************************************************************** From: Raphael Amiard Sent: Monday, October 3, 2016 2:01 PM > How much of a difference would there be to code the example above > using the proposed generator syntax? I suspect there wouldn't be > significant difference in terms of ease of expression. No, I agree that your abstraction is quite expressive, and that there would likely be little difference. I detailed in my other answer why I still think generator semantics are useful. (cooperative, synchronous, deterministic, etc). > It strikes me that this buffer implementation might actually be more > efficient than the generator approach. With the generator syntax, my > understanding is that a stack context switch needs to occur back and > forth every time another value is read. With the buffer approach, the > task typically has the next values to be read already sitting in the > buffer, and to read the buffer, there is no context switch needed. Well, it depends on the implementation of the buffer, but if OS-level synchronization is involved, you'll probably have a system-call and a full context switch, which is much more costly than a stack switch. Anyway, we're clearly getting in the world of "let's profile this" :). Since we have a library-based generator implementation already, and your generator generic, I'll try to whip-up some benchmarks before the ARG meeting in Pittsburgh ! **************************************************************** From: Brad Moore Sent: Monday, October 3, 2016 2:23 PM That would be good to see, but I think streaming is slow in Ada, and not necessary for a generator. Also my buffer libraries were not designed for speed. It might be a better comparison to replace with the standard synchronized_queues library instead. **************************************************************** From: Raphael Amiard Sent: Monday, October 3, 2016 2:27 PM > That would be good to see, but I think streaming is slow in Ada, and not >necessary for a generator. Also my buffer libraries were not designed for speed. >It might be a better comparison to replace with the standard >synchronized_queues library instead. No problem, I can use the synchronized queues instead of the streaming buffers, it seems like quite a minor change. **************************************************************** From: Florian Schanda Sent: Tuesday, October 4, 2016 5:08 AM > 3. Determinism. You control the order of execution of your generator. > It doesn't matter in simple examples, but is a big big plus of > generators in the real world. I think all your points are really good (and I agree with all of them), but to me this is the single most important point. I think its plausible that an implementation *may* use a task behind the scenes, if it could somehow guarantee that nothing happens that would differ from these semantics, but to me that is an optimisation detail that we should not go into in the RM. **************************************************************** From: Raphael Amiard Sent: Tuesday, October 4, 2016 1:37 PM Tucker, I'm amending my initial proposal, and I don't understand your suggestion below: >>What is missing from your proposal is, how do you go from the first form >>to the second. So, I have this Positive_Generator type declared >>somewhere, and I have this client as above. Can I use an instance of the >>Prime_Factory type and pass it to next with default ? >> >>1. If yes (which is what I would implicitly expect when reading your >> proposal), then from what I can see, you have some of the same >> problems that you'd have with the 'Generator approach: Is a generator >> type yielding a Natural compatible with the Positive_Generator type ? >> >>2. If no, then you'd have to explicitly specify in the implementation >> that it is deriving from Positive_Generator, which breaks the >> modularity principle, and is annoying in practice: > >I believe Steve was requiring only that the yielded subtypes match statically, >which is a pretty well-defined requirement. But then we might want to relax >that a bit to allow for classwide types, and perhaps unconstrained >discriminated types. It turns out the matching rules required for "explicitly >aliased" parameters might be just about right. See RM 6.4.1(6,6.1,6.2): > >"If the formal parameter is an explicitly aliased parameter, [...]. Further, >if the formal parameter subtype F is untagged: >6.1/3 the subtype F shall statically match the nominal subtype of the actual > object; or >6.2/3 the subtype F shall be unconstrained, discriminated in its full view, > and unconstrained in any partial view." >>... It means that you >> cannot use a positive yielding generator implemented by somebody that >> didn't know of your interface. Of course that can be worked around >> with conversion rules (as it is done for other types). You also have >> the "dummy type explosion" problem - Someday I'll count how many >> "access all String" access types we have in GPS, but probably more >> than 10 ! > >I don't think we need to face these problems, if we use something close to >6.1/6.2 above for untagged subtype matching. How do you propose that we use those rules ? can you be more explicit about what you had in mind ? Thanks in advance ! *************************************************************** From: Raphael Amiard Sent: Wednesday, October 5, 2016 1:39 PM I did an updated version of the original AI, integrating Steve's suggestions. [This is version /01 of this alternative - Editor.] **************************************************************** From: Randy Brukardt Sent: Wednesday, October 5, 2016 9:57 PM > I did an updated version of the original AI, integrating Steve's > suggestions This is AI12-0197-3/01 (that is, the third alternative of the generator proposal). I find it interesting that you essentially finished Steve's homework for him (but thank you, because I probably wouldn't have had time to do it before the meeting). See my discussion with Florian (for AI12-0127-1) for my take on that. :-) **************************************************************** From: Steve Baird Sent: Wednesday, October 5, 2016 6:35 PM > 'Next means > "run until reaching either a yield statement of the end of the > generator typo: first "of" => "or" ==== > 3. Specific generator implementations, such as the one above, can be converted > to abstract generator types, provided the yielded subtype statically matches. There might also be accessibility conditions that have to be satisfied in some cases when converting to from a shorter-lived type to a longer-lived type, but presumably these would be handled the same way that the analogous issue is handled with conversions between specific and class-wide types. One way or another we don't want to allow type Positive_Generator yield Positive; type Ref is access Positive_Generator; Ptr : Ref; procedure P is generator type Local_Generator is ...; function F yield Local_Generator is ...; begin Ptr := new Local_Generator'(F); to execute successfully. The proposal doesn't talk about the detail of whether an explicit conversion is required vs. allowing the concrete-to-abstract conversion to be done implicitly, as for a specific-to-classwide conversion; if an explicit conversion is required that would solve this problem but it would also make these guys harder to use because "type conversion" isn't one of the constructs on the 7.5(2.1/5) list (the "aggregates, function calls, and their friends" list). It seems like following the existing model for conversions between class-wide and specific tagged types would be cleanest. ==== > We propose introducing these new object declarations: > > generator_type_declaration ::= Perhaps delete the word "object"? ==== > Note that this code is already working code, using a runtime library > that was developed on top of a portable stack switching library called PCL. Would this work in the build-in-place case (e.g., if the generated type is Some_Limited_Type'Class)? ==== Some questions we have discussed, but were not mentioned in the proposal (which is fine, except that I'm curious): a) are yield statements allowed in nested subprograms (unlike accept statements), with appropriate runtime checks to detect "inappropriate" execution of a yield statement? b) does an attempt to execute a yield statement during the execution of another yield statement raise P_E? (as we have discussed, I think it should). c) are users are responsible for preventing unsynchronized access (as with predefined container types)? **************************************************************** From: Raphael Amiard Sent: Thursday, October 6, 2016 9:17 AM >> 'Next means >> "run until reaching either a yield statement of the end of the >> generator > > typo: first "of" => "or" Will fix, thanks ! > There might also be accessibility conditions that have to be satisfied > in some cases when converting to from a shorter-lived type to a > longer-lived type, but presumably these would be handled the same way > that the analogous issue is handled with conversions between specific > and class-wide types. > > One way or another we don't want to allow > > type Positive_Generator yield Positive; > type Ref is access Positive_Generator; > Ptr : Ref; > > procedure P is > generator type Local_Generator is ...; > > function F yield Local_Generator is ...; > begin > Ptr := new Local_Generator'(F); > > to execute successfully. Can I just write in the AI (for the time being): 3. Specific generator implementations, such as the one above, can be converted to abstract generator types, provided the yielded subtype statically matches, and that the specific generator type satisfies the same rules towards the abstract generator type as in the case of a conversion between a specific and a class-wide type. > The proposal doesn't talk about the detail of whether an explicit > conversion is required vs. allowing the concrete-to-abstract > conversion to be done implicitly, as for a specific-to-classwide > conversion; if an explicit conversion is required that would solve > this problem but it would also make these guys harder to use because > "type conversion" isn't one of the constructs on the 7.5(2.1/5) list (the > "aggregates, function calls, and their friends" list). > > It seems like following the existing model for conversions between > class-wide and specific tagged types would be cleanest. Yes it doesn't talk about it because I didn't understand your and Tuck's views on the matter :) This makes it a bit clearer for me. > ==== > >> We propose introducing these new object declarations: >> >> generator_type_declaration ::= > > Perhaps delete the word "object"? > You're right, will fix. > ==== > >> Note that this code is already working code, using a runtime library >> that was developed on top of a portable stack switching library called PCL. > > Would this work in the build-in-place case (e.g., if the generated > type is Some_Limited_Type'Class)? > Probably not :) I'll have to check. When designing the prototype (and the first version of this AI) we didn't even think about limited types much. So I guess the real underlying question is "can it be made to work with B-I-P and limited types". I have no idea, so that can be some homework for the next ARG meeting. > ==== > > Some questions we have discussed, but were not mentioned in the > proposal (which is fine, except that I'm curious): > > a) are yield statements allowed in nested subprograms (unlike accept > statements), with appropriate runtime checks to detect > "inappropriate" execution of a yield statement? Yes, I actually sent the wrong version of the file to this thread, because I added it in the last version. > b) does an attempt to execute a yield statement during > the execution of another yield statement raise P_E? > (as we have discussed, I think it should). > Yes, another thing I forgot ! Adding it > c) are users are responsible for preventing unsynchronized access > (as with predefined container types)? > Yes. I'll specify that as well. Thanks for the review Steve ! **************************************************************** From: Raphael Amiard Sent: Thursday, October 6, 2016 10:44 AM >> I did an updated version of the original AI, integrating Steve's >> suggestions > This is AI12-0197-3/01 (that is, the third alternative of the > generator proposal). Yes, absolutely. I find Steve's proposal much better than my original one: It is very close to the desired semantics of my proposal, while being much more Ada-idiomatic as far as definition and use of generators go. > I find it interesting that you essentially finished Steve's homework > for him He also in some way started my homework for me, and you have one less proposal to read, so everybody wins ;) Here is my amended version of it integrating Steve's remarks - I think it's still time right ? [This is version /02 of the AI - Editor.] **************************************************************** From: Tucker Taft Sent: Thursday, October 6, 2016 10:17 PM >> I don't think we need to face these problems, if we use something >> close to 6.1/6.2 above for untagged subtype matching. > > How do you propose that we use those rules ? can you be more explicit > about what you had in mind ? I think I was suggesting that the matching rules between the yielded type of an abstract generator and the yielded type of a concrete generator be based on the rules used for matching between a formal aliased parameter and the actual parameter specified in 6.4.1(6.1-6.2). **************************************************************** From: Jean-Pierre Rosen Sent: Friday, October 7, 2016 8:28 AM Since it seems quite unsure whether we can have a telecon tomorrow, here is a summary of my position. 1) Generators are an implementation detail. Any package (or ADT) with a Get_Next function and a Has_More_Elements function is a generator. Whether a whole structure is constructed, or some magic gizmo produces elements one by one is, and should be, invisible to the caller. 2) There are many ways a generator can be implemented using the current features of the language. For example, attached [See the end of this message - Editor] is the prime number generator implemented as an ADT, without tasks. A bit longer due to the look-ahead required by Is_Terminated, but that's all. Ada is about building-blocks. We already have the necessary building blocks. We may add some others that can be useful to generators (like passive tasks or value returning entries), but only if they have more usages than just generators (which is, in my opinion, the case for these two). 3) Benefits do not outweigh the cost I see a whole new syntax, with lots of semantic difficulties in the proposal for a feature that (AFAIK) has not been asked for by any casual user (AdaCore correct me if I'm wrong). And I can imagine many more difficulties: what if generators are nested? what happens to nested tasks when a generator is suspended? etc. Moreove, I heartidly agree that we should not make the language too frightening for implementors who did not (yet) catch up with the latest version. What Ada needs is not more features, it's more vendors! 4) I don't buy the motivations from the AI. 1. Non-determinism. Tasks execution is preemptive and thus non-deterministic. It means that any access to non-synchronized outer variables is non safe by default. Scheduling can be controlled, and Ada offers lots of features to that effect. Moreover, passive tasks would be deterministic. But more importantly, a generator implemented by a task is a typical example where you simply don't care when it runs (except that it could use spare cycles of hyper-threaded processors - a good thing in my view). I don't see why a generator implemented by a task would need to refer to global variables. OTOH, a generator as proposed could have a local task accessing global variables. This argument is really a red herring: if you are afraid of global variables, don't use them! Variables local to a task are all that's needed to keep a state. 2. Synchronization overhead. This stems from point 1, but when you need a deterministic synchronization point, you'll pay for it in performance. Assorted is the general overhead of starting/stopping a task for short lived iterators. Tasking is not so bad, and moreover generators need full context switching, therefore it must first be shown that generator switching is significantly faster than task switching. And (sorry for repeating myself), tasking is just one possible way of implementing generators. I'm quite confident that most of them would be implemented with ADT, or plain packages, or queues, or.... 5) Python people like it Sure. But remember that Python has no abstract data types, no information hiding, no packages - and no decent tasking. -------------------------------- PS: I didn't write the AI on passive tasks because I don't think it should be discussed in the context of generators. It should be a proposal on its own. (All the best if it is also useful for implementing generators). --------- with Text_IO; use Text_IO; with System; procedure Test_Gen2 is package Primer is type Prime_Factory (Sieve_Size : Natural) is tagged private; function Next (Generator : in out Prime_Factory) return Positive with Post => Next'Result <= Generator.Sieve_Size; function Is_Terminated (Generator : in Prime_Factory) return Boolean; private type Sieve is array (Positive range <>) of Boolean; -- tagged not necessary, just here to allow prefixed notation and keep -- OO maniacs quiet. type Prime_Factory (Sieve_Size : Natural) is tagged record Is_Composite : Sieve (2 .. Sieve_Size) := (others => False); Current : Positive := 2; Is_Terminated : Boolean := False; end record; end Primer; package body Primer is procedure Mark_Multiples (Prime : Positive; Into : in out Prime_Factory) is Multiple : Positive := Prime; begin loop Into.Is_Composite (Multiple) := True; exit when Multiple > Into.Sieve_Size - Prime; Multiple := Multiple + Prime; end loop; end Mark_Multiples; function Next (Generator : in out Prime_Factory) return Positive is Result : Positive; begin if Generator.Is_Terminated then raise Constraint_Error; -- or whatever end if; Result := Generator.Current; Mark_Multiples (Prime => Generator.Current, Into => Generator); while Generator.Current <= Generator.Sieve_Size loop if not Generator.Is_Composite (Generator.Current) then return Result; end if; Generator.Current := Generator.Current + 1; end loop; Generator.Is_Terminated := True; return Result; end Next; function Is_Terminated (Generator : in Prime_Factory) return Boolean is begin return Generator.Is_Terminated; end Is_Terminated; end Primer; use Primer; My_Gen : Prime_Factory (100); Prime : Positive; begin while not My_Gen.Is_Terminated loop Prime := My_Gen.Next; Put_Line (Positive'image(Prime)); end loop; end Test_Gen2; **************************************************************** From: Raphael Amiard Sent: Saturday, October 8, 2016 7:12 AM ... > 1) Generators are an implementation detail. > Any package (or ADT) with a Get_Next function and a Has_More_Elements > function is a generator. Whether a whole structure is constructed, or > some magic gizmo produces elements one by one is, and should be, > invisible to the caller. Indeed, generators are an implementation detail to the caller. It was asserted multiple times during the previous meeting that generators are useful to the implementer, and that to the caller they're just iterators. That does not make them useless, eg. the big missing part of your sentence is "they're an implementation detail *to the caller*". > 2) There are many ways a generator can be implemented using the > current features of the language. > For example, attached is the prime number generator implemented as an > ADT, without tasks. A bit longer due to the look-ahead required by > Is_Terminated, but that's all. Well thank you for providing that, it's an interesting comparison. To my eye it is a perfect rationale of why generators are useful. On the other hand, saying that it's just "a bit longer but that's all" seems pretty disingenuous to me, since you're omitting the fact that it is also quite a bit more complicated. Ada is supposed to be about readability, and your example is much less readable (even though it is very well written), not in terms of lines of code but in terms of operational complexity, because 80% of your code is actually boilerplate maintaining the state of your iterator, and 20% is the sieve logic. The fact that this is already so apparent on an example so small that it can fit into an AI is in my opinion a very good counter argument to your whole line of reasoning on generators. > Ada is about building-blocks. We already have the necessary building > blocks. You assert that as it is a fact, without providing any evidence in this mail- actually providing counter evidence in my opinion. The only viable alternative IMHO from the point of view of expressivity is doing this sieve as a (regular) task. > 3) Benefits do not outweigh the cost > I see a whole new syntax, with lots of semantic difficulties in the > proposal for a feature that (AFAIK) has not been asked for by any > casual user (AdaCore correct me if I'm wrong). And I can imagine many > more > difficulties: what if generators are nested? what happens to nested > tasks when a generator is suspended? etc. Your full input on those difficulties would be appreciated regardless of whether you are for integrating the feature or not. > Moreove, I heartidly agree that we should not make the language too > frightening for implementors who did not (yet) catch up with the > latest version. What Ada needs is not more features, it's more vendors! Well, this is always a compromise between the perceived usefulness of the feature and the perceived complexity of the implementation. With that said, I need to say that we are *already* implementing new features for the next version of Ada, so saying that "Ada doesn't need more features" in that context sounds a bit strange ! > 4) I don't buy the motivations from the AI. > 1. Non-determinism. Tasks execution is preemptive and thus > non-deterministic. It means that any access to non-synchronized > outer variables is non safe by default. > > Scheduling can be controlled, and Ada offers lots of features to that > effect. Moreover, passive tasks would be deterministic. Yes, as I already said, passive tasks would be an interesting substitute for generators in my opinion. You cannot make the point that generators are useless and passive tasks are not however, because they provide exactly the same kind of semantics.. > But more > importantly, a generator implemented by a task is a typical example > where you simply don't care when it runs (except that it could use > spare cycles of hyper-threaded processors - a good thing in my view). That's true only for simple examples. There's plenty of examples where you do actually care, and where you *want* determinism and access to outer scope state. There is an incremental highlighter based on generators in GPS that follows such a design, that would be extremely hard to conceive with tasks. > I don't see why a generator implemented by a task would need to refer > to global variables. OTOH, a generator as proposed could have a local > task accessing global variables. This argument is really a red > herring: if you are afraid of global variables, don't use them! > Variables local to a task are all that's needed to keep a state. Are you saying that unsynchronized access to state outside of a task is a red-herring ? That's a pretty weird statement in my opinion, and completely disconnected from state of the art knowledge about multi-threaded programming. > 2. Synchronization overhead. This stems from point 1, but when you > need a deterministic synchronization point, you'll pay for it in > performance. Assorted is the general overhead of > starting/stopping a task for short lived iterators. > > Tasking is not so bad, and moreover generators need full context > switching, therefore it must first be shown that generator switching is > significantly faster than task switching. We agree that it must be benchmarked. > And (sorry for repeating myself), tasking is just one possible way of > implementing generators. I'm quite confident that most of them would be > implemented with ADT, or plain packages, or queues, or.... Yes they can, and it's painful and bug prone hence the need for this feature. Saying that you can implement X with Y does not strike me as very useful in discussions about language design. You can do object oriented programming in C, and by that same logic, adding an object oriented layer to any language is useless. > 5) Python people like it > Sure. But remember that Python has no abstract data types, no > information hiding, no packages - and no decent tasking. What is your point ? None of those language features except tasking give you anything close to generators. **************************************************************** From: Brad Moore Sent: Friday, October 7, 2016 10:15 AM >> > But for the generator library abstraction I presented, the use of a >> > > > task is an implementation detail. > > It is not an implementation detail I think: > > 1. If you access any outer variable that is not part of the task body, > you'll have potential race conditions. If you access synchronized > objects you'll have potential deadlocks, etc.. You have all the > problems of task based programming. > > 2. Even for the use of the synchronization buffer, you'll have > synchronization involved, which means overhead, but also a potential > system call on some systems, which can be a very bad thing if you're > calling that in a tight (soft-realtime) loop. > > 3. Determinism. You control the order of execution of your generator. > It doesn't matter in simple examples, but is a big big plus of > generators in the real world. > > 4. Those simpler characteristics also mean that the resulting feature > will be *much* easier to use in some embedded footprints. Determinism > + reduced runtime support means that it's much easier to certify code > using generators than to certify code using tasks. It also means that > having support in ZFP/SFP runtimes will also be much easier to > implement. If I had implemented the buffer such that it only held one object, and that the generator did not fetch the value for that object until the client had blocked on a call to read the buffer, then I think there would be no potential race conditions, and it would be deterministic, since only one task would be progressing the usage of the generator at a time. As for synchronization overhead, that sounds like something that might be addressed by some compiler optimization, or by using parallelism. I also have doubts that most users wouldn't be happy with the performance using a task based solution. I suspect that people interested in determinism are not necessarily that interested in performance speed, and vice versa those interested in speed are not so interested in determinism. It also remains to be seen whether the python generator approach offers significant performance benefits. So I remain unconvinced so far, but interested to hear the discussion. **************************************************************** From: Raphael Amiard Sent: Saturday, October 8, 2016 7:34 AM > If I had implemented the buffer such that it only held one object, and > that the generator did not fetch the value for that object until the > client had blocked on a call to read the buffer, then I think there > would be no potential race conditions, and it would be deterministic, > since only one task would be progressing the usage of the generator at a > time. That's True, but you would just have happened to make a deterministic program containing tasks. That's not impossible but it can get pretty difficult and requires following a certain discipline that the compiler cannot force you to follow. Generators (and passive tasks) on the other hand, are *always* deterministic, and that's where they're interesting for developers, but also for certification and proof. Even if you made a mistake, altered the wrong variable, implemented the wrong algorithm, you'll always get the same result. > As for synchronization overhead, that sounds like something that might > be addressed by some compiler optimization, or by using parallelism. In some instances the parallelism will be a benefit. In others, what you want to express is mainly sequential, so synchronization will be the main thing your processor spends its time upon. I think a tree traversal will be one of those examples. > I > also have doubts that most users wouldn't be happy with the > performance using a task based solution. Well that's clearly an unknown I agree. > I suspect that people interested in determinism are not necessarily > that interested in performance speed, and vice versa those interested > in speed are not so interested in determinism. I want both :) But more seriously, I think it's a whole package. We also have some customers who cannot use tasks at all, and are running on mono processors. Tasks are also a hassle to add to ZFP (zero footprint) runtimes, where generators could be easier to add. > It also remains to be seen whether the python generator approach > offers significant performance benefits. It seems to me that this is the main question I need to answer now. Unfortunately I didn't have time to do the benchmarks before this ARG meeting, so I'm afraid it will remain an unknown for now. Thank you for the thorough feedback **************************************************************** From: Raphael Amiard Sent: Monday, June 12, 2016 4:10 AM > AI12-0197-3 (with help from Steve Baird) As mentioned in a previous mail, I have been thinking a bit about generators and the bigger picture. I think generators/coroutines would fit better as a language defined library unit. If we sum up the current state of the discussion: 1. The standardization effort would be very substantial 2. A lot of people in the ARG are not convinced that the feature is interesting enough to warrant inclusion as a language feature 3. The only benefit that a language level solution has on a library is the amount of boilerplate you have to declare a generator 4. 3 could probably be alleviated by orthogonal and more generally useful improvements to the language I will hence write another proposal, for generators as a library, and withdraw this one, if that's OK with everyone of course. ****************************************************************