• project euler 26

    From CSYH (QAQ)@21:1/5 to All on Mon Sep 4 02:19:51 2023
    I am new to Ada, I know is there a good way to start this program?
    thanks
    https://projecteuler.net/problem=26

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Niklas Holsti@21:1/5 to All on Mon Sep 4 14:06:13 2023
    On 2023-09-04 12:19, CSYH (QAQ) wrote:
    I am new to Ada, I know is there a good way to start this program?
    thanks
    https://projecteuler.net/problem=26


    First invent/discover the method (algorithm) for solving the problem,
    without thinking about the programming language.

    I don't think any language has built-in features that would lead to a
    direct solution, although some functional language with lazy evaluation
    could come close, because such languages can manipulate unbounded
    (potentially infinite) sequences of values. Such sequences can be
    handled in Ada, too, but with more effort -- they are not "built in" to Ada.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to Niklas Holsti on Mon Sep 4 14:39:17 2023
    On 2023-09-04 13:06, Niklas Holsti wrote:
    On 2023-09-04 12:19, CSYH (QAQ) wrote:
    I am new to Ada, I know is there a good way to start this program?
    thanks
    https://projecteuler.net/problem=26

    First invent/discover the method (algorithm) for solving the problem,
    without thinking about the programming language.

    I don't think any language has built-in features that would lead to a
    direct solution, although some functional language with lazy evaluation
    could come close, because such languages can manipulate unbounded (potentially infinite) sequences of values. Such sequences can be
    handled in Ada, too, but with more effort -- they are not "built in" to
    Ada.

    Infinite division does not require big numbers, which Ada 22 has, but I
    wound not use them anyway because the performance would be abysmal.

    BTW, Ada is perfect for numeric algorithms no need to resort to
    functional mess... (:-))

    The problem itself requires as you said mathematical analysis, because a
    naive method of comparing partial division result with itself is
    obviously wrong. E.g. let you have

    0.12341234...

    you could not conclude that the period is (1234) because it could
    actually be (123412345).

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to All on Mon Sep 4 16:23:54 2023
    On 2023-09-04 11:19, CSYH (QAQ) wrote:
    I am new to Ada, I know is there a good way to start this program?
    thanks
    https://projecteuler.net/problem=26

    Ok, I leave it to you checking if my implementation is correct. -------------------test.adb----------
    with Ada.Strings.Unbounded; use Ada.Strings.Unbounded;
    with Ada.Text_IO; use Ada.Text_IO;

    procedure Test is

    N : constant := 1000;

    function Period (Divisor : Positive) return String is
    type Remainder is record
    Index : Positive;
    Value : Positive;
    end record;
    Result : String (1..N);
    Value : Integer := 1;
    Remainders : array (1..N) of Remainder;
    begin
    for Index in Result'Range loop
    Value := Value * 10;
    Result (Index) :=
    Character'Val (Character'Pos ('0') + Value / Divisor);
    Value := Value mod Divisor;
    if Value = 0 then
    return ""; -- Non-periodic
    end if;
    if Index > 1 then
    for Item in 1..Index - 1 loop
    declare
    This : Remainder renames Remainders (Item);
    begin
    if Value = This.Value then
    return Result (This.Index + 1..Index);
    end if;
    end;
    end loop;
    end if;
    Remainders (Index) := (Index, Value);
    end loop;
    raise Constraint_Error with "Period calculation error";
    end Period;

    Max_Period : Unbounded_String;
    Max_Divisor : Positive;
    begin
    for Divisor in 2..999 loop
    declare
    This : constant String := Period (Divisor);
    begin
    if This /= "" then
    Put_Line
    ( "1 /"
    & Integer'Image (Divisor)
    & " has "
    & This
    & " in period"
    );
    end if;
    if Length (Max_Period) < This'Length then
    Max_Period := To_Unbounded_String (This);
    Max_Divisor := Divisor;
    end if;
    end;
    end loop;
    Put_Line
    ( "The first longest period is "
    & To_String (Max_Period)
    & " in 1 /"
    & Integer'Image (Max_Divisor)
    );
    end Test;
    -------------------test.adb----------
    It gives the longest period for 1/983.

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to Dmitry A. Kazakov on Mon Sep 4 17:01:04 2023
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-04 13:06, Niklas Holsti wrote:
    On 2023-09-04 12:19, CSYH (QAQ) wrote:
    I am new to Ada, I know is there a good way to start this program?
    thanks
    https://projecteuler.net/problem=26
    First invent/discover the method (algorithm) for solving the problem,
    without thinking about the programming language.
    I don't think any language has built-in features that would lead to a
    direct solution, although some functional language with lazy evaluation
    could come close, because such languages can manipulate unbounded
    (potentially infinite) sequences of values. Such sequences can be handled
    in Ada, too, but with more effort -- they are not "built in" to Ada.

    Infinite division does not require big numbers, which Ada 22 has, but I
    wound not use them anyway because the performance would be abysmal.

    BTW, Ada is perfect for numeric algorithms no need to resort to functional mess... (:-))

    Perfect? That's a bold claim!

    Mind you, I don't think this problem is really a numerical one in that
    sense. It needs some simple integer arithmetic but then every language
    is perfect for that sort of arithmetic.

    Using a functional mess (Haskell) a simple, native solution (i.e. using
    no modules) is only 9 lines long.

    I don't want to start a language war. Ada is just more 'wordy' by
    deliberate design so a simple Ada solution is inevitably going to be
    longer in terms of lines. Rather my purpose in posting is to steer the
    OP away from thinking of this as a numerical problem in the classical
    sense. It really isn't.

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to Ben Bacarisse on Mon Sep 4 21:20:56 2023
    On 2023-09-04 18:01, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-04 13:06, Niklas Holsti wrote:
    On 2023-09-04 12:19, CSYH (QAQ) wrote:
    I am new to Ada, I know is there a good way to start this program?
    thanks
    https://projecteuler.net/problem=26
    First invent/discover the method (algorithm) for solving the problem,
    without thinking about the programming language.
    I don't think any language has built-in features that would lead to a
    direct solution, although some functional language with lazy evaluation
    could come close, because such languages can manipulate unbounded
    (potentially infinite) sequences of values. Such sequences can be handled >>> in Ada, too, but with more effort -- they are not "built in" to Ada.

    Infinite division does not require big numbers, which Ada 22 has, but I
    wound not use them anyway because the performance would be abysmal.

    BTW, Ada is perfect for numeric algorithms no need to resort to functional >> mess... (:-))

    Perfect? That's a bold claim!

    Ada is a very improved descendant of Algol 60, which was designed to
    codify algorithms.

    Mind you, I don't think this problem is really a numerical one in that
    sense. It needs some simple integer arithmetic but then every language
    is perfect for that sort of arithmetic.

    That is still all about algorithms (rather than about for example
    building abstractions as in the case of OOP)

    Using a functional mess (Haskell) a simple, native solution (i.e. using
    no modules) is only 9 lines long.

    Apart from the fundamental inconsistency of functional paradigm:
    computing is about transition of states and nothing else; the imperative languages express solutions, i.e. an algorithm. Functional, and in
    general, declarative languages express puzzles.

    They remind me a math examination tasks on studying a function. Here is
    a definition. Go figure out the properties and behavior...

    Or, if you want, functional is like a chess composition: white to move
    and checkmate in 4 moves. Challenging, but Ada is about playing chess.

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to Ben Bacarisse on Mon Sep 4 23:00:25 2023
    On 2023-09-04 22:18, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-04 18:01, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    BTW, Ada is perfect for numeric algorithms no need to resort to functional >>>> mess... (:-))
    Perfect? That's a bold claim!

    Ada is a very improved descendant of Algol 60, which was designed to codify >> algorithms.

    Yes, though I was respond to you narrower remark about being perfect for numeric algorithms.

    Yes, Ada is.

    Are you expending that to perfect for every kind of
    algorithm?

    Algorithms are defined in terms of established types, e.g. model numbers
    or other well known structures. Ada works pretty good for non-numeric algorithms too. So well, that many Ada programmers never go beyond this
    stage and proclaim anathema to anything above it.

    (rather than about for example building
    abstractions as in the case of OOP)

    That's interesting. You don't consider using functions and procedures (possibly higher-order ones) to be a way to build abstractions?

    No, they do not introduce new types and do not form some structure of
    their values. And "using" is not an abstraction anyway.

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to Dmitry A. Kazakov on Mon Sep 4 21:18:16 2023
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-04 18:01, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-04 13:06, Niklas Holsti wrote:
    On 2023-09-04 12:19, CSYH (QAQ) wrote:
    I am new to Ada, I know is there a good way to start this program?
    thanks
    https://projecteuler.net/problem=26
    First invent/discover the method (algorithm) for solving the problem,
    without thinking about the programming language.
    I don't think any language has built-in features that would lead to a
    direct solution, although some functional language with lazy evaluation >>>> could come close, because such languages can manipulate unbounded
    (potentially infinite) sequences of values. Such sequences can be handled >>>> in Ada, too, but with more effort -- they are not "built in" to Ada.

    Infinite division does not require big numbers, which Ada 22 has, but I
    wound not use them anyway because the performance would be abysmal.

    BTW, Ada is perfect for numeric algorithms no need to resort to functional >>> mess... (:-))
    Perfect? That's a bold claim!

    Ada is a very improved descendant of Algol 60, which was designed to codify algorithms.

    Yes, though I was respond to you narrower remark about being perfect for numeric algorithms. Are you expending that to perfect for every kind of algorithm?

    Mind you, I don't think this problem is really a numerical one in that
    sense. It needs some simple integer arithmetic but then every language
    is perfect for that sort of arithmetic.

    That is still all about algorithms

    Yes but, again, that's not what I was responding to.

    (rather than about for example building
    abstractions as in the case of OOP)

    That's interesting. You don't consider using functions and procedures (possibly higher-order ones) to be a way to build abstractions?

    Using a functional mess (Haskell) a simple, native solution (i.e. using
    no modules) is only 9 lines long.

    Apart from the fundamental inconsistency of functional paradigm: computing
    is about transition of states and nothing else; the imperative languages express solutions, i.e. an algorithm. Functional, and in general,
    declarative languages express puzzles.

    Rather than try to unpick that paragraph I'll just say that they can,
    none the less, give simple solutions to this sort of programming
    problem.

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to Dmitry A. Kazakov on Tue Sep 5 00:16:47 2023
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-04 22:18, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-04 18:01, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    BTW, Ada is perfect for numeric algorithms no need to resort to functional
    mess... (:-))
    Perfect? That's a bold claim!

    Ada is a very improved descendant of Algol 60, which was designed to codify >>> algorithms.
    Yes, though I was respond to you narrower remark about being perfect for
    numeric algorithms.

    Yes, Ada is.

    :-)

    (rather than about for example building
    abstractions as in the case of OOP)

    That's interesting. You don't consider using functions and procedures
    (possibly higher-order ones) to be a way to build abstractions?

    No, they do not introduce new types and do not form some structure of their values. And "using" is not an abstraction anyway.

    The term "abstraction" is usually taken to be more general than that so
    as to include function (or procedural) abstraction.

    Ada is good at that, but the syntax is sufficiently cumbersome that I
    think it discourages people from exploiting that part of the language.
    Mind you, I am no Ada expert so maybe it's simpler to do than I think.

    Here's my Ada solution:

    with Ada.Text_IO; use Ada.Text_IO;
    with Ada.Containers.Ordered_Maps; use Ada.Containers;

    procedure Euler_26 is

    function Period(Divisor: Positive) return Positive is
    Index: Natural := 0;
    Carry: Natural := 1;

    package Carry_Maps is new Ordered_Maps(Natural, Natural);
    use Carry_Maps;
    Carries: Map;
    Loc: Cursor;
    begin
    loop
    Loc := Carries.Find(Carry);
    exit when Loc /= No_Element;
    Carries.Insert(Carry, Index);
    Index := Index + 1;
    Carry := Carry mod Divisor * 10;
    end loop;
    return Index - Element(Loc);
    end Period;

    Max_Period: Natural := 1;
    Divisor_With_Max_Period: Natural := 1;
    begin
    for D in 2..999 loop
    declare Ds_Period: constant Positive := Period(D);
    begin
    if Ds_Period > Max_Period
    then
    Divisor_With_Max_Period := D;
    Max_Period := Ds_Period;
    end if;
    end;
    end loop;
    Put_Line(Integer'Image(Divisor_With_Max_Period));
    end Euler_26;

    The part that finds the D that maximises Period(D) is just boilerplate
    code. I know this can be abstracted out in Ada, but I think the syntax
    is messy. I was hoping to find (or be able to write) a generic function
    that takes an 'iterable' (if that's the right word) and a function, and
    which returns the element that maximises the function. I got stuck
    trying. Maybe someone can help?

    I know it won't make this program shorter, but it would be interesting
    to know how it might be done.

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to Ben Bacarisse on Tue Sep 5 09:23:46 2023
    On 2023-09-05 01:16, Ben Bacarisse wrote:

    The term "abstraction" is usually taken to be more general than that so
    as to include function (or procedural) abstraction.

    These are means of software decomposition rather than abstraction (of something).

    Ada is good at that, but the syntax is sufficiently cumbersome that I
    think it discourages people from exploiting that part of the language.
    Mind you, I am no Ada expert so maybe it's simpler to do than I think.

    If the program does not resemble electric transmission noise, some
    people call the language syntax cumbersome... (:-))

    Here's my Ada solution:

    with Ada.Text_IO; use Ada.Text_IO;
    with Ada.Containers.Ordered_Maps; use Ada.Containers;

    procedure Euler_26 is

    function Period(Divisor: Positive) return Positive is

    You cannot use a number here because the period may have leading zeros.

    I know it won't make this program shorter, but it would be interesting
    to know how it might be done.

    The goal of engineering is not making programs shorter, it is to make
    them understandable, safer, reusable, maintainable, extensible, integrable.

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to Dmitry A. Kazakov on Tue Sep 5 16:18:16 2023
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-05 01:16, Ben Bacarisse wrote:

    The term "abstraction" is usually taken to be more general than that so
    as to include function (or procedural) abstraction.

    These are means of software decomposition rather than abstraction (of something).

    That's not how the word is usually used. Obviously I can't (and don't
    want to) change your mind, but algorithms can be abstracted as well as
    data.

    I was hoping someone could how me how in for the example program I gave
    since that's an area of Ada I am not familiar with (but I's sure it's possible).

    Ada is good at that, but the syntax is sufficiently cumbersome that I
    think it discourages people from exploiting that part of the language.
    Mind you, I am no Ada expert so maybe it's simpler to do than I think.

    If the program does not resemble electric transmission noise, some people call the language syntax cumbersome... (:-))

    That's true. But there are also constructs that are genuinely
    cumbersome in some languages. Anyway, to find out more, I was hoping
    someone would show me what it looks like in Ada -- I outlined what I
    wanted to do after the code I posted.

    Here's my Ada solution:
    with Ada.Text_IO; use Ada.Text_IO;
    with Ada.Containers.Ordered_Maps; use Ada.Containers;
    procedure Euler_26 is
    function Period(Divisor: Positive) return Positive is

    You cannot use a number here because the period may have leading
    zeros.

    The function returns the decimal period of 1/Divisor. I don't believe
    there is a bug, but if you think you've found one, I'd like to know
    about it.

    Of course there can be leading zeros, but my algorithm ignores the
    digits and determines the period using the "carry" instead.

    I know it won't make this program shorter, but it would be interesting
    to know how it might be done.

    The goal of engineering is not making programs shorter, it is to make them understandable, safer, reusable, maintainable, extensible, integrable.

    Yes. That's exactly why I was asking for someone who knows Ada better
    to show me how to write the reusable component I described. There was
    boiler plate code in my program that could be abstracted out into a
    generic function (or package?) so that any function can be maximised
    over some range or, better yet, any iterable type (if that's how Ada
    does things).

    Can someone here show me how?

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to Ben Bacarisse on Tue Sep 5 19:08:59 2023
    On 2023-09-05 17:18, Ben Bacarisse wrote:

    There was
    boiler plate code in my program that could be abstracted out into a
    generic function (or package?) so that any function can be maximised
    over some range or, better yet, any iterable type (if that's how Ada
    does things).

    Can someone here show me how?

    You define some classes. Either generic or tagged. E.g. a generic class
    of functions that uses two generic classes of the argument and the value:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type)
    return Argument_Type is <>;
    with function "<" (Left, Right : Argument_Type)
    return Boolean is <>;
    with function "=" (Left, Right : Argument_Type)
    return Boolean is <>;
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type ) return Boolean is <>;
    -- Function type
    with function Func (Argument : Argument_Type) return Value_Type;
    function Generic_Maximum_At (Left, Right : Argument_Type)
    return Value_Type;

    and the implementation

    function Generic_Maximum_At (Left, Right : Argument_Type)
    return Value_Type is
    Argument : Argument_Type := Left;
    Max : Value_Type;
    Value : Value_Type;
    begin
    if Right < Left then
    raise Constraint_Error with "Empty interval";
    end if;
    Max := Func (Argument);
    while not (Argument = Right) loop
    Argument := Next (Argument);
    Value := Func (Argument);
    if Max < Value then
    Max := Value;
    end if;
    end loop;
    return Max;
    end Generic_Maximum_At;

    or you can choose to pass the function as an argument:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type)
    return Argument_Type is <>;
    with function "<" (Left, Right : Argument_Type)
    return Boolean is <>;
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type) return Boolean is <>;
    function Generic_Maximum_At
    ( Left, Right : Argument_Type;
    Func : access function (Argument : Argument_Type)
    return Value_Type
    ) return Value_Type;

    Or you can make it a package which is usually a better choice as one can
    pack into it several entities sharing the same generic interface:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type)
    return Argument_Type is <>;
    with function "<" (Left, Right : Argument_Type )
    return Boolean is <>;
    with function "=" (Left, Right : Argument_Type)
    return Boolean is <>;
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type) return Boolean is <>;
    package Generic_Discrete_Comparable_Valued is
    function Maximum_At
    ( Left, Right : Argument_Type;
    Func : access function (Argument : Argument_Type)
    return Value_Type
    ) return Value_Type;
    -- Other useless functions
    end Generic_Discrete_Comparable_Valued;

    The generic classes of arguments/values can be in turn factored out into reusable generic packages:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type) return Argument_Type is <>;
    with function "<" (Left, Right : Argument_Type) return Boolean is <>;
    with function "=" (Left, Right : Argument_Type) return Boolean is <>; package Generic_Arguments is
    end Generic_Arguments;

    generic
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type ) return Boolean is <>;
    package Generic_Values is
    end Generic_Values;

    generic
    with package Arguments is new Generic_Arguments (<>);
    with package Values is new Generic_Values (<>);
    package Generic_Discrete_Comparable_Valued is
    use Arguments, Values;
    function Maximum_At
    ( Left, Right : Argument_Type;
    Func : access function (Argument : Argument_Type)
    return Value_Type
    ) return Value_Type;
    -- Other useless functions
    end Generic_Discrete_Comparable_Valued;

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From moi@21:1/5 to Dmitry A. Kazakov on Tue Sep 5 18:35:10 2023
    On 05/09/2023 08:23, Dmitry A. Kazakov wrote:
    On 2023-09-05 01:16, Ben Bacarisse wrote:

    The term "abstraction" is usually taken to be more general than that so
    as to include function (or procedural) abstraction.

    These are means of software decomposition rather than abstraction (of something).

    They are both of these things, actually.


    Ada is good at that, but the syntax is sufficiently cumbersome that I
    think it discourages people from exploiting that part of the language.
    Mind you, I am no Ada expert so maybe it's simpler to do than I think.

    If the program does not resemble electric transmission noise, some
    people call the language syntax cumbersome... (:-))

    8-)

    Here's my Ada solution:

    with Ada.Text_IO; use Ada.Text_IO;
    with Ada.Containers.Ordered_Maps; use Ada.Containers;

    procedure Euler_26 is

        function Period(Divisor: Positive) return Positive is

    You cannot use a number here because the period may have leading zeros.

    I know it won't make this program shorter, but it would be interesting
    to know how it might be done.

    The goal of engineering is not making programs shorter, it is to make
    them understandable, safer, reusable, maintainable, extensible, integrable.

    Hear, hear!

    Functionalists do seem to have an obsession with brevity at all costs.
    It's very strange.

    --
    Bill F.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to Dmitry A. Kazakov on Wed Sep 6 02:10:23 2023
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-05 17:18, Ben Bacarisse wrote:

    There was
    boiler plate code in my program that could be abstracted out into a
    generic function (or package?) so that any function can be maximised
    over some range or, better yet, any iterable type (if that's how Ada
    does things).

    Can someone here show me how?

    You define some classes. Either generic or tagged. E.g. a generic class of functions that uses two generic classes of the argument and the value:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type)
    return Argument_Type is <>;
    with function "<" (Left, Right : Argument_Type)
    return Boolean is <>;
    with function "=" (Left, Right : Argument_Type)
    return Boolean is <>;
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type ) return Boolean is <>;
    -- Function type
    with function Func (Argument : Argument_Type) return Value_Type;
    function Generic_Maximum_At (Left, Right : Argument_Type)
    return Value_Type;

    and the implementation

    function Generic_Maximum_At (Left, Right : Argument_Type)
    return Value_Type is
    Argument : Argument_Type := Left;
    Max : Value_Type;
    Value : Value_Type;
    begin
    if Right < Left then
    raise Constraint_Error with "Empty interval";
    end if;
    Max := Func (Argument);
    while not (Argument = Right) loop
    Argument := Next (Argument);
    Value := Func (Argument);
    if Max < Value then
    Max := Value;
    end if;
    end loop;
    return Max;
    end Generic_Maximum_At;

    or you can choose to pass the function as an argument:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type)
    return Argument_Type is <>;
    with function "<" (Left, Right : Argument_Type)
    return Boolean is <>;
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type) return Boolean is <>; function Generic_Maximum_At
    ( Left, Right : Argument_Type;
    Func : access function (Argument : Argument_Type)
    return Value_Type
    ) return Value_Type;

    Or you can make it a package which is usually a better choice as one can
    pack into it several entities sharing the same generic interface:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type)
    return Argument_Type is <>;
    with function "<" (Left, Right : Argument_Type )
    return Boolean is <>;
    with function "=" (Left, Right : Argument_Type)
    return Boolean is <>;
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type) return Boolean is <>;
    package Generic_Discrete_Comparable_Valued is
    function Maximum_At
    ( Left, Right : Argument_Type;
    Func : access function (Argument : Argument_Type)
    return Value_Type
    ) return Value_Type;
    -- Other useless functions
    end Generic_Discrete_Comparable_Valued;

    The generic classes of arguments/values can be in turn factored out into reusable generic packages:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type) return Argument_Type is <>;
    with function "<" (Left, Right : Argument_Type) return Boolean is <>;
    with function "=" (Left, Right : Argument_Type) return Boolean is <>; package Generic_Arguments is
    end Generic_Arguments;

    generic
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type ) return Boolean is <>; package Generic_Values is
    end Generic_Values;

    generic
    with package Arguments is new Generic_Arguments (<>);
    with package Values is new Generic_Values (<>);
    package Generic_Discrete_Comparable_Valued is
    use Arguments, Values;
    function Maximum_At
    ( Left, Right : Argument_Type;
    Func : access function (Argument : Argument_Type)
    return Value_Type
    ) return Value_Type;
    -- Other useless functions
    end Generic_Discrete_Comparable_Valued;

    Thank you. I can't yet see how to use any of these alternatives, but
    that's my problem. Are there any good online sources on Ada generic programming so I can find out how to implement and use this short of
    package?

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to Ben Bacarisse on Wed Sep 6 09:06:31 2023
    On 2023-09-06 03:10, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-05 17:18, Ben Bacarisse wrote:

    There was
    boiler plate code in my program that could be abstracted out into a
    generic function (or package?) so that any function can be maximised
    over some range or, better yet, any iterable type (if that's how Ada
    does things).

    Can someone here show me how?

    You define some classes. Either generic or tagged. E.g. a generic class of >> functions that uses two generic classes of the argument and the value:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type)
    return Argument_Type is <>;
    with function "<" (Left, Right : Argument_Type)
    return Boolean is <>;
    with function "=" (Left, Right : Argument_Type)
    return Boolean is <>;
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type ) return Boolean is <>;
    -- Function type
    with function Func (Argument : Argument_Type) return Value_Type;
    function Generic_Maximum_At (Left, Right : Argument_Type)
    return Value_Type;

    and the implementation

    function Generic_Maximum_At (Left, Right : Argument_Type)
    return Value_Type is
    Argument : Argument_Type := Left;
    Max : Value_Type;
    Value : Value_Type;
    begin
    if Right < Left then
    raise Constraint_Error with "Empty interval";
    end if;
    Max := Func (Argument);
    while not (Argument = Right) loop
    Argument := Next (Argument);
    Value := Func (Argument);
    if Max < Value then
    Max := Value;
    end if;
    end loop;
    return Max;
    end Generic_Maximum_At;

    or you can choose to pass the function as an argument:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type)
    return Argument_Type is <>;
    with function "<" (Left, Right : Argument_Type)
    return Boolean is <>;
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type) return Boolean is <>;
    function Generic_Maximum_At
    ( Left, Right : Argument_Type;
    Func : access function (Argument : Argument_Type)
    return Value_Type
    ) return Value_Type;

    Or you can make it a package which is usually a better choice as one can
    pack into it several entities sharing the same generic interface:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type)
    return Argument_Type is <>;
    with function "<" (Left, Right : Argument_Type )
    return Boolean is <>;
    with function "=" (Left, Right : Argument_Type)
    return Boolean is <>;
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type) return Boolean is <>;
    package Generic_Discrete_Comparable_Valued is
    function Maximum_At
    ( Left, Right : Argument_Type;
    Func : access function (Argument : Argument_Type)
    return Value_Type
    ) return Value_Type;
    -- Other useless functions
    end Generic_Discrete_Comparable_Valued;

    The generic classes of arguments/values can be in turn factored out into
    reusable generic packages:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type) return Argument_Type is <>; >> with function "<" (Left, Right : Argument_Type) return Boolean is <>;
    with function "=" (Left, Right : Argument_Type) return Boolean is <>;
    package Generic_Arguments is
    end Generic_Arguments;

    generic
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type ) return Boolean is <>;
    package Generic_Values is
    end Generic_Values;

    generic
    with package Arguments is new Generic_Arguments (<>);
    with package Values is new Generic_Values (<>);
    package Generic_Discrete_Comparable_Valued is
    use Arguments, Values;
    function Maximum_At
    ( Left, Right : Argument_Type;
    Func : access function (Argument : Argument_Type)
    return Value_Type
    ) return Value_Type;
    -- Other useless functions
    end Generic_Discrete_Comparable_Valued;

    Thank you. I can't yet see how to use any of these alternatives, but
    that's my problem.

    It is pretty much straightforward. E.g. the last one:

    package Arguments is new Generic_Arguments (Integer, Integer'Succ);
    package Values is new Generic_Values (Integer);
    package Functions is
    new Generic_Discrete_Comparable_Valued (Arguments, Values);

    Now you can print the maximum of your Period function:

    Put_Line
    ( "Max at"
    & Integer'Image (Functions.Maximum_At (2, 999, Period'Access))
    );

    Are there any good online sources on Ada generic
    programming so I can find out how to implement and use this short of
    package?

    Actually I provided an implementation above. Here it is again:

    package body Generic_Discrete_Comparable_Valued is
    function Maximum_At
    ( Left, Right : Argument_Type;
    Func : access function (Argument : Argument_Type)
    return Value_Type
    ) return Value_Type is
    Argument : Argument_Type := Left;
    Max : Value_Type;
    Value : Value_Type;
    begin
    if Right < Left then
    raise Constraint_Error with "Empty interval";
    end if;
    Max := Func (Argument);
    while not (Argument = Right) loop
    Argument := Next (Argument);
    Value := Func (Argument);
    if Max < Value then
    Max := Value;
    end if;
    end loop;
    return Max;
    end Maximum_At;
    end Generic_Discrete_Comparable_Valued;

    (The packages Generic_Arguments and Generic_Values have no bodies)

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to Ben Bacarisse on Wed Sep 6 17:54:47 2023
    On 2023-09-06 17:16, Ben Bacarisse wrote:

    I am curious to know how reusable this is. Can the packages be
    instantiated in such a way that the argument ranges over the elements
    of, say, and Ordered_Map?

    Sure:

    with Ada.Containers.Ordered_Maps;

    package Integer_Maps is
    new Ada.Containers.Ordered_Maps (Integer, Integer);
    use Integer_Maps;
    package Cursor_Arguments is new Generic_Arguments (Cursor);
    package Map_Values is new Generic_Values (Integer);
    package Map_Functions is
    new Generic_Discrete_Comparable_Valued
    (Cursor_Arguments, Map_Values);

    Then given X is a map: X : Map;

    Map_Functions.Maximum_At (X.First, X.Last, Element'Access)

    Maybe a more generic a solution would involve passing something that can
    be iterated over, rather than two values of an "enumerated" type? I
    mean enumerated in the mathematical sense -- it may be the wrong word in
    Ada.

    Yes, but Ada does not have built-in range types. Therefore such design
    will not work out of the box with discrete types because 2..999 is not a
    proper object in Ada. However, talking about abstractions, you can
    create an interval type for the purpose or else use an ordered set of
    integers.

    I am asking you but I am also the group. I appreciate your help,
    but don't want you to feel any obligation to keep helping!

    No problem.

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to Dmitry A. Kazakov on Wed Sep 6 16:16:48 2023
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-06 03:10, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-05 17:18, Ben Bacarisse wrote:

    There was
    boiler plate code in my program that could be abstracted out into a
    generic function (or package?) so that any function can be maximised
    over some range or, better yet, any iterable type (if that's how Ada
    does things).

    Can someone here show me how?

    You define some classes. Either generic or tagged. E.g. a generic class of >>> functions that uses two generic classes of the argument and the value:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type)
    return Argument_Type is <>;
    with function "<" (Left, Right : Argument_Type)
    return Boolean is <>;
    with function "=" (Left, Right : Argument_Type)
    return Boolean is <>;
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type ) return Boolean is <>;
    -- Function type
    with function Func (Argument : Argument_Type) return Value_Type;
    function Generic_Maximum_At (Left, Right : Argument_Type)
    return Value_Type;

    and the implementation

    function Generic_Maximum_At (Left, Right : Argument_Type)
    return Value_Type is
    Argument : Argument_Type := Left;
    Max : Value_Type;
    Value : Value_Type;
    begin
    if Right < Left then
    raise Constraint_Error with "Empty interval";
    end if;
    Max := Func (Argument);
    while not (Argument = Right) loop
    Argument := Next (Argument);
    Value := Func (Argument);
    if Max < Value then
    Max := Value;
    end if;
    end loop;
    return Max;
    end Generic_Maximum_At;

    or you can choose to pass the function as an argument:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type)
    return Argument_Type is <>;
    with function "<" (Left, Right : Argument_Type)
    return Boolean is <>;
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type) return Boolean is <>;
    function Generic_Maximum_At
    ( Left, Right : Argument_Type;
    Func : access function (Argument : Argument_Type)
    return Value_Type
    ) return Value_Type;

    Or you can make it a package which is usually a better choice as one can >>> pack into it several entities sharing the same generic interface:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type)
    return Argument_Type is <>;
    with function "<" (Left, Right : Argument_Type )
    return Boolean is <>;
    with function "=" (Left, Right : Argument_Type)
    return Boolean is <>;
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type) return Boolean is <>;
    package Generic_Discrete_Comparable_Valued is
    function Maximum_At
    ( Left, Right : Argument_Type;
    Func : access function (Argument : Argument_Type)
    return Value_Type
    ) return Value_Type;
    -- Other useless functions
    end Generic_Discrete_Comparable_Valued;

    The generic classes of arguments/values can be in turn factored out into >>> reusable generic packages:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Next (Value : Argument_Type) return Argument_Type is <>; >>> with function "<" (Left, Right : Argument_Type) return Boolean is <>; >>> with function "=" (Left, Right : Argument_Type) return Boolean is <>; >>> package Generic_Arguments is
    end Generic_Arguments;

    generic
    -- Comparable value
    type Value_Type is private;
    with function "<" (Left, Right : Value_Type ) return Boolean is <>;
    package Generic_Values is
    end Generic_Values;

    generic
    with package Arguments is new Generic_Arguments (<>);
    with package Values is new Generic_Values (<>);
    package Generic_Discrete_Comparable_Valued is
    use Arguments, Values;
    function Maximum_At
    ( Left, Right : Argument_Type;
    Func : access function (Argument : Argument_Type)
    return Value_Type
    ) return Value_Type;
    -- Other useless functions
    end Generic_Discrete_Comparable_Valued;
    Thank you. I can't yet see how to use any of these alternatives, but
    that's my problem.

    It is pretty much straightforward. E.g. the last one:

    Sure, but I am new to Ada. Well actually I first wrote Ada in the early
    80s, but the project didn't go with Ada (too new I suspect) so reading
    one book was the extent of my learning.

    package Arguments is new Generic_Arguments (Integer, Integer'Succ);
    package Values is new Generic_Values (Integer);

    I'd probably choose more generic names for the packages since these are
    more general than the names suggest. I might go with Generic_Enumerated
    (since it has 'Next') and Generic_Ordered.

    Just to test I knew what was going on, I changed 'while not (Argument =
    Right)' to 'while Argument < Right' so as to remove the need for having
    an "=" function. I doubt there are any types with "<" but not "=" but I
    wanted to confirm I understood the code.

    package Functions is
    new Generic_Discrete_Comparable_Valued (Arguments, Values);


    Now you can print the maximum of your Period function:

    Put_Line
    ( "Max at"
    & Integer'Image (Functions.Maximum_At (2, 999, Period'Access))
    );

    Thanks.

    (A minor issue: to meet the specification we either need 1000 here or
    the loop needs to be changed to include the upper bound (like the for
    loop did in the original). Whilst it's easy to pass "one past the top
    index" for Integer and so on, if the code can be made more generic it
    would have to use all the values in the range because Ada has not done
    the C++ hack of having XXX.end() be an iterator "one past" the actual
    end of a range.)

    I am curious to know how reusable this is. Can the packages be
    instantiated in such a way that the argument ranges over the elements
    of, say, and Ordered_Map? In some languages (C++!) one could pass a
    pair of iterators here (cursors, I think in Ada-speak). I tried to do
    that but I don't think Ada's cursors are ordered by < though they do
    have a Next function. And if that method does work (it's quite likely
    it was only my ignorance of the language that stopped it working) would
    it work for built-in arrays which don't seem to have cursors.

    Maybe a more generic a solution would involve passing something that can
    be iterated over, rather than two values of an "enumerated" type? I
    mean enumerated in the mathematical sense -- it may be the wrong word in
    Ada.

    I am asking you but I am also the group. I appreciate your help,
    but don't want you to feel any obligation to keep helping!

    Are there any good online sources on Ada generic
    programming so I can find out how to implement and use this short of
    package?

    Actually I provided an implementation above. Here it is again:

    Sorry, missed that first time round.

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to Dmitry A. Kazakov on Thu Sep 7 00:32:21 2023
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-06 17:16, Ben Bacarisse wrote:

    I am curious to know how reusable this is. Can the packages be
    instantiated in such a way that the argument ranges over the elements
    of, say, and Ordered_Map?

    Sure:

    with Ada.Containers.Ordered_Maps;

    package Integer_Maps is
    new Ada.Containers.Ordered_Maps (Integer, Integer);
    use Integer_Maps;
    package Cursor_Arguments is new Generic_Arguments (Cursor);

    Ah! So the arguments correspond to the "with" functions in the order
    listed, and, since Cursor already has Next, there no need to specify
    anything. One could (I've just tried) use => notation. You could have
    written

    package Arguments is new Generic_Arguments (Next => Positive'Succ,
    Argument_Type => Positive);

    in your first example -- swapping the order just to make the point
    obvious. This tripped me up when I was playing around with a Cursors
    solution.

    There are a couple of details that prevent your Maximum_At function from working properly in this case though. First, we can't have an empty
    map, because X.Last can't be compared with X.First when either is
    No_Element, so the test for Right < Left fails before the desired error
    can be raised.

    Second, if I try to use a Vector rather than an Ordered_Map, I am told
    that:

    test2.adb:97:05: error: instantiation error at line 12
    test2.adb:97:05: error: no visible subprogram matches the specification for "<"

    It would seem that vector cursors can't be compared using < (at least by default). Maybe the installation needs more arguments.

    Anyway, I am still not sure how to write a generic test for an empty
    range.

    package Map_Values is new Generic_Values (Integer);
    package Map_Functions is
    new Generic_Discrete_Comparable_Valued
    (Cursor_Arguments, Map_Values);

    Then given X is a map: X : Map;

    Map_Functions.Maximum_At (X.First, X.Last, Element'Access)

    It's possible I was not clear about what I was aiming for. I was hoping
    to be able to find the maximum of some arbitrary function, taking the function's arguments from any sequential collection. Either a simple
    range of values, an array or vector of values, a list of values or even
    an ordered map of values -- any ordered list of values.

    The bottom line is the last argument should be something very general
    like the Period function.

    A fix (though it's not really ideal) would be to use function
    composition here (inventing . as the composition operator):

    Map_Functions.Maximum_At (X.First, X.Last, Period'Access . Element'Access)

    but I don't think Ada has a function composition operator, does it?

    Another solution would be to write Maximum_At so that it knows it has a
    cursor argument, but then I don't think it would work for native arrays,
    would it? And we'd loose plain ranges altogether.

    Maybe a more generic a solution would involve passing something that can
    be iterated over, rather than two values of an "enumerated" type? I
    mean enumerated in the mathematical sense -- it may be the wrong word in
    Ada.

    Yes, but Ada does not have built-in range types. Therefore such design will not work out of the box with discrete types because 2..999 is not a proper object in Ada. However, talking about abstractions, you can create an interval type for the purpose or else use an ordered set of integers.

    But then (I think) the only function one could pass would be something
    like Element as in you example above. Using an ordered set of integers
    would not allow

    Map_Functions.Maximum_At (Set.First, Set.Last, Period'Access)

    would it?

    I am asking you but I am also the group. I appreciate your help,
    but don't want you to feel any obligation to keep helping!

    No problem.

    You seem to be on your own as far as helping out is concerned!

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Francesc Rocher@21:1/5 to All on Thu Sep 7 00:31:09 2023
    El dia dilluns, 4 de setembre de 2023 a les 11:19:53 UTC+2, CSYH (QAQ) va escriure:
    I am new to Ada, I know is there a good way to start this program?
    thanks
    https://projecteuler.net/problem=26

    Hi CSHY,

    Please take a look at my Euler tools repository, https://github.com/rocher/euler_tools (not the best math lib you'll find, I know).
    I used this library tools to solve problem 26 here: https://github.com/rocher/alice-project_euler-rocher
    Let me know what you think.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to Ben Bacarisse on Thu Sep 7 11:02:05 2023
    On 2023-09-07 01:32, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-06 17:16, Ben Bacarisse wrote:

    I am curious to know how reusable this is. Can the packages be
    instantiated in such a way that the argument ranges over the elements
    of, say, and Ordered_Map?

    Sure:

    with Ada.Containers.Ordered_Maps;

    package Integer_Maps is
    new Ada.Containers.Ordered_Maps (Integer, Integer);
    use Integer_Maps;
    package Cursor_Arguments is new Generic_Arguments (Cursor);

    Ah! So the arguments correspond to the "with" functions in the order
    listed, and, since Cursor already has Next, there no need to specify anything.

    Yes, because the formal argument is

    with function Next (Value : Argument_Type)
    return Argument_Type is <>;

    If it were

    with function Next (Value : Argument_Type)
    return Argument_Type;

    You would have to specify the actual. The part "is <>" tells to match a
    visible function Next.

    There are a couple of details that prevent your Maximum_At function from working properly in this case though. First, we can't have an empty
    map, because X.Last can't be compared with X.First when either is
    No_Element, so the test for Right < Left fails before the desired error
    can be raised.

    Yes, cursors is bad idea, in the end they all are pointers. No_Element
    is an equivalent of null which shows.

    However Maximum_At will propagate Constraint_Error if either of the
    bounds is No_Element. So the implementation would work.

    Second, if I try to use a Vector rather than an Ordered_Map, I am told
    that:

    test2.adb:97:05: error: instantiation error at line 12
    test2.adb:97:05: error: no visible subprogram matches the specification for "<"

    It would seem that vector cursors can't be compared using < (at least by default). Maybe the installation needs more arguments.

    Vector has a proper index type. All you have to do is. Given

    package Integer_Vectors is
    new Ada.Containers.Vectors (Integer, Integer);

    Wrap Element into a function:

    V : Integer_Vectors.Vector;
    function Element (Index : Integer) return Integer is
    begin
    return V.Element (Index);
    end Element;
    ...

    and use the wrapper.

    Anyway, I am still not sure how to write a generic test for an empty
    range.

    The problem is that the implementation of Cursor that breaks
    abstraction. The abstraction of an argument does not permit ideal
    non-values. Cursors and pointers have non-values. So if you want to test
    for non-values ahead, instead of surprising the function, you need to
    add a test for value validity to the abstraction:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Valid (Value : Argument_Type) return Boolean is <>;
    ...
    package Generic_Arguments is

    Then you would pass Has_Element for it. For integers you would use
    wrapped X'Valid (there is no Integer'Valid, unfortunately. Only X'Valid
    where X is an object).

    It's possible I was not clear about what I was aiming for. I was hoping
    to be able to find the maximum of some arbitrary function, taking the function's arguments from any sequential collection.

    That is a different abstraction. You need a generic collection instead
    of generic ordered values. E.g.

    generic
    with package Arguments is new Ada.Containers.Ordered_Sets (<>);
    with package Values is new Generic_Values (<>);
    package Generic_Comparable_Valued is
    use Arguments, Values;
    function Maximum_At
    ( Domain : Set;
    Func : access function (Argument : Element_Type)
    return Value_Type
    ) return Value_Type;
    -- Other useless functions
    end Generic_Comparable_Valued;

    package body Generic_Comparable_Valued is
    function Maximum_At
    ( Domain : Set;
    Func : access function (Argument : Element_Type)
    return Value_Type
    ) return Value_Type is
    Max : Value_Type;
    Value : Value_Type;
    Position : Cursor;
    begin
    if Domain.Is_Empty then
    raise Constraint_Error with "Empty set";
    end if;
    Position := Domain.First;
    Max := Func (Element (Position));
    while Position /= Domain.Last loop
    Position := Next (Position);
    Value := Func (Element (Position));
    if Max < Value then
    Max := Value;
    end if;
    end loop;
    return Max;
    end Maximum_At;
    end Generic_Comparable_Valued;

    Either a simple
    range of values, an array or vector of values, a list of values or even
    an ordered map of values -- any ordered list of values.

    In practice such abstraction have too much physical and mental overhead.
    E.g. large sets of values implemented differently from Ada.Containers.Ordered_Sets depending on the operations required. For
    example, let you need a set complement? Usually programmers simply stick
    with software patterns instead. Too much reliance of libraries make
    programs incoherent.

    The bottom line is the last argument should be something very general
    like the Period function.

    A fix (though it's not really ideal) would be to use function
    composition here (inventing . as the composition operator):

    Map_Functions.Maximum_At (X.First, X.Last, Period'Access . Element'Access)

    but I don't think Ada has a function composition operator, does it?

    No as it would require closures. So you can have a generic composition operator, no problem, but not a first-class one. However you can simply
    add Maximum_At with four arguments to the package.

    Another solution would be to write Maximum_At so that it knows it has a cursor argument, but then I don't think it would work for native arrays, would it? And we'd loose plain ranges altogether.

    You can write a generic package creating array cursors:

    generic
    type Index_Type is (<>);
    type Element_Type is private;
    type Array_Type is array (Index_Type range <>) of Element_Type;
    package Array_Cursors is
    type Cursor is private;
    function First (Container : Array_Type) return Cursor;
    function Element (Position : Cursor) return Element_Type;
    function "<" (Left, Right : Cursor) return Boolean;
    ...
    private
    package Dirty_Tricks is
    new System.Address_To_Access_Conversions (Array_Type);
    use Dirty_Tricks;
    type Cursor is record
    Domain : Object_Pointer;
    Index : Index_Type;
    end record;
    end Array_Cursors;

    package body Array_Cursors is
    function "<" (Left, Right : Cursor) return Boolean is
    begin
    if Left.Domain = null or else Left.Domain /= Right.Domain then
    raise Constraint_Error with "Incomparable cursors";
    end if;
    return Left.Index < Right.Index;
    end "<";

    function Element (Position : Cursor) return Element_Type is
    begin
    if Position.Domain = null or else
    Position.Index not in Position.Domain'Range
    then
    raise Constraint_Error with "Invalid cursor";
    else
    return Position.Domain (Position.Index);
    end if;
    end Element;

    function First (Container : Array_Type) return Cursor is
    begin
    if Container'Length = 0 then
    raise Constraint_Error with "Empty array";
    else
    return (To_Pointer (Container'Address), Container'First);
    end if;
    end First;

    end Array_Cursors;

    But then (I think) the only function one could pass would be something
    like Element as in you example above. Using an ordered set of integers
    would not allow

    Map_Functions.Maximum_At (Set.First, Set.Last, Period'Access)

    would it?

    Ordered_Set cursors are ordered like Ordered_Map ones, so it should work.

    I am asking you but I am also the group. I appreciate your help,
    but don't want you to feel any obligation to keep helping!

    No problem.

    You seem to be on your own as far as helping out is concerned!

    Because it started as a numeric puzzle. You should have asked directly
    about generics or tagged types instead.

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to Dmitry A. Kazakov on Fri Sep 8 02:32:00 2023
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-07 01:32, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-06 17:16, Ben Bacarisse wrote:

    I am curious to know how reusable this is. Can the packages be
    instantiated in such a way that the argument ranges over the elements
    of, say, and Ordered_Map?

    Sure:

    with Ada.Containers.Ordered_Maps;

    package Integer_Maps is
    new Ada.Containers.Ordered_Maps (Integer, Integer);
    use Integer_Maps;
    package Cursor_Arguments is new Generic_Arguments (Cursor);
    Ah! So the arguments correspond to the "with" functions in the order
    listed, and, since Cursor already has Next, there no need to specify
    anything.

    Yes, because the formal argument is

    with function Next (Value : Argument_Type)
    return Argument_Type is <>;

    If it were

    with function Next (Value : Argument_Type)
    return Argument_Type;

    You would have to specify the actual. The part "is <>" tells to match a visible function Next.

    Thanks. I remember that now. Given Ada's preference for words, it's a mysterious choice.

    There are a couple of details that prevent your Maximum_At function from
    working properly in this case though. First, we can't have an empty
    map, because X.Last can't be compared with X.First when either is
    No_Element, so the test for Right < Left fails before the desired error
    can be raised.

    Yes, cursors is bad idea, in the end they all are pointers. No_Element is
    an equivalent of null which shows.

    However Maximum_At will propagate Constraint_Error if either of the bounds
    is No_Element. So the implementation would work.

    Sure, but ideally we want the error we decided on for this situation.
    Since the intent is to be generic, it's a shame to get one error with
    some instantiations and a different one with others.

    Second, if I try to use a Vector rather than an Ordered_Map, I am told
    that:
    test2.adb:97:05: error: instantiation error at line 12
    test2.adb:97:05: error: no visible subprogram matches the specification for "<"
    It would seem that vector cursors can't be compared using < (at least by
    default). Maybe the installation needs more arguments.

    Vector has a proper index type. All you have to do is. Given

    package Integer_Vectors is
    new Ada.Containers.Vectors (Integer, Integer);

    Wrap Element into a function:

    V : Integer_Vectors.Vector;
    function Element (Index : Integer) return Integer is
    begin
    return V.Element (Index);
    end Element;
    ...

    and use the wrapper.

    Sure, but the hope was to write something that does not need new
    code for new situations. That's what makes it reusable.

    Anyway, I am still not sure how to write a generic test for an empty
    range.

    The problem is that the implementation of Cursor that breaks
    abstraction. The abstraction of an argument does not permit ideal
    non-values. Cursors and pointers have non-values. So if you want to test
    for non-values ahead, instead of surprising the function, you need to add a test for value validity to the abstraction:

    generic
    -- Ordered argument
    type Argument_Type is private;
    with function Valid (Value : Argument_Type) return Boolean is <>;
    ...
    package Generic_Arguments is

    Then you would pass Has_Element for it. For integers you would use wrapped X'Valid (there is no Integer'Valid, unfortunately. Only X'Valid where X is
    an object).

    It's definitely getting what I call cumbersome.

    It's possible I was not clear about what I was aiming for. I was hoping
    to be able to find the maximum of some arbitrary function, taking the
    function's arguments from any sequential collection.

    That is a different abstraction. You need a generic collection instead of generic ordered values. E.g.

    generic
    with package Arguments is new Ada.Containers.Ordered_Sets (<>);
    with package Values is new Generic_Values (<>);
    package Generic_Comparable_Valued is
    use Arguments, Values;
    function Maximum_At
    ( Domain : Set;
    Func : access function (Argument : Element_Type)
    return Value_Type
    ) return Value_Type;
    -- Other useless functions
    end Generic_Comparable_Valued;

    package body Generic_Comparable_Valued is
    function Maximum_At
    ( Domain : Set;
    Func : access function (Argument : Element_Type)
    return Value_Type
    ) return Value_Type is
    Max : Value_Type;
    Value : Value_Type;
    Position : Cursor;
    begin
    if Domain.Is_Empty then
    raise Constraint_Error with "Empty set";
    end if;
    Position := Domain.First;
    Max := Func (Element (Position));
    while Position /= Domain.Last loop
    Position := Next (Position);
    Value := Func (Element (Position));
    if Max < Value then
    Max := Value;
    end if;
    end loop;
    return Max;
    end Maximum_At;
    end Generic_Comparable_Valued;

    Either a simple
    range of values, an array or vector of values, a list of values or even
    an ordered map of values -- any ordered list of values.

    In practice such abstraction have too much physical and mental
    overhead. E.g. large sets of values implemented differently from Ada.Containers.Ordered_Sets depending on the operations required. For example, let you need a set complement? Usually programmers simply stick
    with software patterns instead. Too much reliance of libraries make
    programs incoherent.

    The core of my Haskell solution is just a function decimalRepeatLength
    that returns the repeat length given a divisor. But once I'd got the
    answer (by applying it to 2 to 999 and getting the maximum) I wondered
    what would happen if the numbers were not in a simple range. Is it easy
    to write a `maximisedOver` function that finds the maximum of some
    function over any ordered collection (technically, a "foldable" type in Haskell).

    Well, yes, it is easy:

    function `maximisedOver` anything = maximum (fmap function anything)

    so the solution to the project Euler problem is just

    decimalRepeatLength `maximisedOver` [2..999]

    but I can also find the maximum of this (or any other suitable) function
    over an array, a hash map, a vector... whatever. No code changes
    anywhere. It even works with arrays of any number of dimensions
    regardless of the index bounds.

    maximisedOver is genuinely generic and reusable.

    I don't think this is incoherent. The Haskell libraries ensure that any collection that is logically foldable is indeed foldable.

    The bottom line is the last argument should be something very general
    like the Period function.
    A fix (though it's not really ideal) would be to use function
    composition here (inventing . as the composition operator):
    Map_Functions.Maximum_At (X.First, X.Last, Period'Access
    . Element'Access)
    but I don't think Ada has a function composition operator, does it?

    No as it would require closures.

    What closure is required for a function composition? There is no
    environment to "close over".

    So you can have a generic composition
    operator, no problem, but not a first-class one. However you can simply add Maximum_At with four arguments to the package.

    This may be the closest we can get with Ada.

    Another solution would be to write Maximum_At so that it knows it has a
    cursor argument, but then I don't think it would work for native arrays,
    would it? And we'd loose plain ranges altogether.

    You can write a generic package creating array cursors:

    generic
    type Index_Type is (<>);
    type Element_Type is private;
    type Array_Type is array (Index_Type range <>) of Element_Type;
    package Array_Cursors is
    type Cursor is private;
    function First (Container : Array_Type) return Cursor;
    function Element (Position : Cursor) return Element_Type;
    function "<" (Left, Right : Cursor) return Boolean;
    ...
    private
    package Dirty_Tricks is
    new System.Address_To_Access_Conversions (Array_Type);
    use Dirty_Tricks;
    type Cursor is record
    Domain : Object_Pointer;
    Index : Index_Type;
    end record;
    end Array_Cursors;

    package body Array_Cursors is
    function "<" (Left, Right : Cursor) return Boolean is
    begin
    if Left.Domain = null or else Left.Domain /= Right.Domain then
    raise Constraint_Error with "Incomparable cursors";
    end if;
    return Left.Index < Right.Index;
    end "<";

    function Element (Position : Cursor) return Element_Type is
    begin
    if Position.Domain = null or else
    Position.Index not in Position.Domain'Range
    then
    raise Constraint_Error with "Invalid cursor";
    else
    return Position.Domain (Position.Index);
    end if;
    end Element;

    function First (Container : Array_Type) return Cursor is
    begin
    if Container'Length = 0 then
    raise Constraint_Error with "Empty array";
    else
    return (To_Pointer (Container'Address), Container'First);
    end if;
    end First;

    end Array_Cursors;

    That's a lot just to use something that is supposed to be reusable.

    You seem to be on your own as far as helping out is concerned!

    Because it started as a numeric puzzle. You should have asked directly
    about generics or tagged types instead.

    It only occurred to me after writing the non-generic solution. I
    remember Ada as being something of a pioneer in it's attempt to provide
    generic solutions, so I wondered how far things had come. I don't think something really widely reusable is possible in this case.

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From G.B.@21:1/5 to Ben Bacarisse on Fri Sep 8 08:09:55 2023
    On 07.09.23 01:32, Ben Bacarisse wrote:


    A fix (though it's not really ideal) would be to use function
    composition here (inventing . as the composition operator):

    Hm. A stateful, composed function that needs to be applied
    in a certain way. Is that so different from calling interface
    subprograms of a certain type?

    A wild guess: only "monads" would add substantial toppings
    to the commonalities. Considering the computational powers of
    C++'s "hair-raising template metaprogramming" [14.4], the idea
    of "Ada generics" = "functional style" is probably limited
    in scope.

    So, does type composition help?


    [14.4]: A Tour of C++, 3rd ed.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to Ben Bacarisse on Fri Sep 8 09:23:13 2023
    On 2023-09-08 03:32, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-07 01:32, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-06 17:16, Ben Bacarisse wrote:

    Second, if I try to use a Vector rather than an Ordered_Map, I am told
    that:
    test2.adb:97:05: error: instantiation error at line 12
    test2.adb:97:05: error: no visible subprogram matches the specification for "<"
    It would seem that vector cursors can't be compared using < (at least by >>> default). Maybe the installation needs more arguments.

    Vector has a proper index type. All you have to do is. Given

    package Integer_Vectors is
    new Ada.Containers.Vectors (Integer, Integer);

    Wrap Element into a function:

    V : Integer_Vectors.Vector;
    function Element (Index : Integer) return Integer is
    begin
    return V.Element (Index);
    end Element;
    ...

    and use the wrapper.

    Sure, but the hope was to write something that does not need new
    code for new situations. That's what makes it reusable.

    Why should it be? You wanted to find maximum of a function. Vector is
    not a function. It is in mathematical terms, but not in the language
    terms. The abstraction for finding maximum in a container is just a
    different abstraction.

    Then you would pass Has_Element for it. For integers you would use wrapped >> X'Valid (there is no Integer'Valid, unfortunately. Only X'Valid where X is >> an object).

    It's definitely getting what I call cumbersome.

    Yes, because you try too hard to make it work where it probably should not.

    I don't think this is incoherent. The Haskell libraries ensure that any collection that is logically foldable is indeed foldable.

    Ada arrays and library containers do not share interfaces. [It is a long discussion how they could be]. But similarly, there is no shared
    interface between digits of a number in octal base and a container and a
    string in UTF-16 encoding. Should there be? No. Should the language
    allow adding ad-hoc interfaces to existing types. Yes, and this is
    possible in Ada in some very uncomfortable AKA cumbersome way, which is
    why "finding maximum" is not a worthy abstraction in Ada.

    The bottom line is the last argument should be something very general
    like the Period function.
    A fix (though it's not really ideal) would be to use function
    composition here (inventing . as the composition operator):
    Map_Functions.Maximum_At (X.First, X.Last, Period'Access
    . Element'Access)
    but I don't think Ada has a function composition operator, does it?

    No as it would require closures.

    What closure is required for a function composition? There is no
    environment to "close over".

    In Ada a function can use anything visible at its declaration point and
    at the location of its body. You can even declare a function inside a recursively called function and let it see local variables of each
    recursive call, in effect having an infinite set of functions.

    That's a lot just to use something that is supposed to be reusable.

    [rant on]
    An Ada programmer would just write a loop. Abstractions are meant to
    abstract the problem domain. If you starting abstract elementary
    programming activities, then there might be something wrong with the
    language or with you.

    Then there is a point about readability. When I see a loop I say, aha
    this is what the guy is going to do. When I see a pile of calls of a
    dozen generic instances with arbitrary names, I begin to worry.

    In my view it is a road to nowhere, for an imperative language at least.
    The end of this road can be seen in modern C++. 20 years ago C++ was
    severely crippled broken but sometimes enjoyable language. You could
    *read* a C++ program. In these days with all libraries it became Forth
    on steroids. There is no such thing as a C++ program anymore, just calls
    upon calls.
    [rant off]

    It only occurred to me after writing the non-generic solution. I
    remember Ada as being something of a pioneer in it's attempt to provide generic solutions, so I wondered how far things had come. I don't think something really widely reusable is possible in this case.

    As I said you think in a wrong direction of abstracting the language
    "finding maximum" rather than the problem space, e.g. generalization to
    other bases, other mathematical structures etc.

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to G.B. on Fri Sep 8 22:02:36 2023
    "G.B." <bauhaus@notmyhomepage.invalid> writes:

    On 07.09.23 01:32, Ben Bacarisse wrote:


    A fix (though it's not really ideal) would be to use function
    composition here (inventing . as the composition operator):

    Hm. A stateful, composed function that needs to be applied
    in a certain way. Is that so different from calling interface
    subprograms of a certain type?

    There was nothing stateful (as I understand the term) in either function
    being composed.

    As to your question, not being an Ada expert I can't answer. I could
    not see any fix other than passing a composed function which would, it
    seems, have to be written afresh. Is that what your question refers to?
    If so, then yes there is a small difference: writing a function (albeit
    just a few lines) vs. applying an operator to two already written
    functions.

    A wild guess: only "monads" would add substantial toppings
    to the commonalities. Considering the computational powers of
    C++'s "hair-raising template metaprogramming" [14.4], the idea
    of "Ada generics" = "functional style" is probably limited
    in scope.

    So, does type composition help?

    My turn to guess now: you are not being serious? I see no connection to
    monads or type composition. And why bring C++ into it?

    Having found the maximum of the function 'Period' over a range 2..999,
    you might find yourself a week later wanting the maximum absolute value
    of the numbers in an Ordered_Map. And then later the maximum of sine
    squared over the elements of 2D array. You might want to have a
    resuable "maximum of F over X" function, so I was curious about how
    close one could get to this in Ada (or, more accurately, what the
    restrictions on X and F might have to be).

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to Dmitry A. Kazakov on Sat Sep 9 01:25:37 2023
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-08 03:32, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-07 01:32, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-06 17:16, Ben Bacarisse wrote:

    Second, if I try to use a Vector rather than an Ordered_Map, I am told >>>> that:
    test2.adb:97:05: error: instantiation error at line 12
    test2.adb:97:05: error: no visible subprogram matches the specification for "<"
    It would seem that vector cursors can't be compared using < (at least by >>>> default). Maybe the installation needs more arguments.

    Vector has a proper index type. All you have to do is. Given

    package Integer_Vectors is
    new Ada.Containers.Vectors (Integer, Integer);

    Wrap Element into a function:

    V : Integer_Vectors.Vector;
    function Element (Index : Integer) return Integer is
    begin
    return V.Element (Index);
    end Element;
    ...

    and use the wrapper.
    Sure, but the hope was to write something that does not need new
    code for new situations. That's what makes it reusable.

    Why should it be? You wanted to find maximum of a function. Vector is
    not a function.

    I wanted the maximum of a function over a collection (range, array, map,
    etc). In some languages, collections can be scanned so you don't need
    to know where the data come from.

    Then you would pass Has_Element for it. For integers you would use wrapped >>> X'Valid (there is no Integer'Valid, unfortunately. Only X'Valid where X is >>> an object).
    It's definitely getting what I call cumbersome.

    Yes, because you try too hard to make it work where it probably should
    not.

    If you think a resuable Ada function that can find the maximum of some F
    over some 'collection' X is possible, I'd like to see how it's done. I
    can do it for some kinds of X but I have no idea how general it can be
    made in Ada. I think the answer is either that it can't be very
    general, or to make it very general is too much work, or that one should
    not be trying in the first place.

    (I put 'collection' in quotes because I know that's an Ada term but I
    don't necessarily want to restrict the solution to how Ada uses the
    term. For example, I don't think native arrays are collections in the
    formal Ada library sense.)

    I don't think this is incoherent. The Haskell libraries ensure that any
    collection that is logically foldable is indeed foldable.

    Ada arrays and library containers do not share interfaces.

    I was pretty sure that was the case. Thanks for confirming. I think
    that means there can be no truly generic solution. But maybe it's
    possible at least for all container types in the library? (But I note
    that if you think it /shouldn't/ be done, I won't expect you to show me
    how.)

    Should the language allow adding
    ad-hoc interfaces to existing types. Yes, and this is possible in Ada in
    some very uncomfortable AKA cumbersome way, which is why "finding maximum"
    is not a worthy abstraction in Ada.

    I suspected one might have to extend the interfaces. If a simple
    abstraction (maximise F over X) does not have a simple representation,
    it's not going to be worth it. Just write a slightly different empty
    test and loop each time you need to do it.

    A fix (though it's not really ideal) would be to use function
    composition here (inventing . as the composition operator):
    Map_Functions.Maximum_At (X.First, X.Last, Period'Access
    . Element'Access)
    but I don't think Ada has a function composition operator, does it?

    No as it would require closures.
    What closure is required for a function composition? There is no
    environment to "close over".

    In Ada a function can use anything visible at its declaration point and at the location of its body. You can even declare a function inside a recursively called function and let it see local variables of each
    recursive call, in effect having an infinite set of functions.

    At the point where I want Period.Element I can write the (almost)
    one-line function that takes a Cursor and returns Period(Element(C))
    entirely mechanically. Can't the compiler do that?

    Note I'm not asking if it /should/ (it may not be "Ada-like" to do
    that). I'm just curious if there really is a technical reason it can't
    be done.

    That's a lot just to use something that is supposed to be reusable.

    [rant on]
    An Ada programmer would just write a loop.

    Yes, that's fine. Different languages have different objectives. Just
    write the empty range test and the loop you need for each kind of
    collection. That was definitely the way things were done in the 80s.

    It only occurred to me after writing the non-generic solution. I
    remember Ada as being something of a pioneer in it's attempt to provide
    generic solutions, so I wondered how far things had come. I don't think
    something really widely reusable is possible in this case.

    As I said you think in a wrong direction of abstracting the language
    "finding maximum" rather than the problem space, e.g. generalization to
    other bases, other mathematical structures etc.

    Generalising to an arbitrary base is local to the function that finds
    the answer for one element. It's an entirely separate axis of
    generalisation to that of where the elements come from.

    It's interesting to me that you consider one simply wrong and the other natural. In some languages the "wrong" one does not even merit
    consideration as it's just there for free. You can concentrate on the
    other bases and other structures without worrying if the program will be
    able to maximise over the collection in which they are stored. (For
    example, for polynomial residues, they can't come from a range like
    2..999.)

    I really do appreciate your help. I would not have got off the ground
    with generics without your examples. Also, one thing I like about
    Usenet is coming across people with very different ideas about
    programming. In this case, it seems to be about what is worth
    generalising and what isn't.

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From G.B.@21:1/5 to Ben Bacarisse on Sat Sep 9 10:13:44 2023
    On 08.09.23 23:02, Ben Bacarisse wrote:
    "G.B." <bauhaus@notmyhomepage.invalid> writes:

    On 07.09.23 01:32, Ben Bacarisse wrote:


    A fix (though it's not really ideal) would be to use function
    composition here (inventing . as the composition operator):

    Hm. A stateful, composed function that needs to be applied
    in a certain way. Is that so different from calling interface
    subprograms of a certain type?

    There was nothing stateful (as I understand the term) in either function being composed.

    The "apparatus" that the computation needs in order to remember
    "max so far" looks like part of its state to me. Somehow
    "the function" needs to operate this state and evaluate it.
    Extend this to:
    - find the maximum of [the maxima of] these n collections
    - find the maximum in this stream at 10 seconds from now.

    Is it possible, or practical, to define a pure function so that
    calling it will remember the needed information, n >= 0
    being arbitrary?

    So, does type composition help?

    My turn to guess now: you are not being serious? I see no connection to monads or type composition.

    In the following sense:
    There is an object of type So_Far that can remember
    objects of any type T, them coming from collections
    of type C-of-T.

    And why bring C++ into it?

    It's already there, you mentioned the pair of iterators, and
    there is std::max_element() which finds the greatest element
    in any range based solely on these, and optionally using a generic
    comparison.
    There are similar things in Dmitry's packages. A key difference
    seems to be that Ada's Cursors are tied to a specific collection.
    I don't know of any convenient way around this, maybe because
    type Cursor is just private in every Ada.Containers.Xyz and
    there is no common type name for them, or for what some
    algorithm might need them to have in common.

    I'm not sure if the new Ada.Iterator_Interfaces (LRM 5.5.1)
    could solve this, also because I really don't know that yet.
    But it looks like I'd need instances of specific containers
    for instantiation. (That being consistent with Ada's approach
    to the STL, I think.)

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to Ben Bacarisse on Sat Sep 9 11:32:39 2023
    On 2023-09-09 02:25, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-08 03:32, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-07 01:32, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    I wanted the maximum of a function over a collection (range, array, map, etc). In some languages, collections can be scanned so you don't need
    to know where the data come from.

    Hmm, the thing we discussed was a maximum element in array or map rather
    than a maximum of a function over the *domain* set of array or map. In a
    typed language array /= domain of array.

    Then you would pass Has_Element for it. For integers you would use wrapped >>>> X'Valid (there is no Integer'Valid, unfortunately. Only X'Valid where X is >>>> an object).
    It's definitely getting what I call cumbersome.

    Yes, because you try too hard to make it work where it probably should
    not.

    If you think a resuable Ada function that can find the maximum of some F
    over some 'collection' X is possible, I'd like to see how it's done.

    To start with, no such function exists. Not in a typed language. Note
    that a generic function is not a function. So instead we must consider
    language constructs for the purpose. Generic instantiation is one of
    them, some class might be another, but in Ada we just use loops. (And
    yes, people liking writing programs while standing on their heads, may
    use recursion... (:-))

    I
    can do it for some kinds of X but I have no idea how general it can be
    made in Ada. I think the answer is either that it can't be very
    general, or to make it very general is too much work, or that one should
    not be trying in the first place.

    The limits of generality are defined by the interfaces. In Ada types are designed to implement needed interfaces upfront. If you want to do that
    after the fact, you need some other adapter types to shove an existing
    type into something it was not designed for.

    I don't think this is incoherent. The Haskell libraries ensure that any >>> collection that is logically foldable is indeed foldable.

    Ada arrays and library containers do not share interfaces.

    I was pretty sure that was the case. Thanks for confirming. I think
    that means there can be no truly generic solution. But maybe it's
    possible at least for all container types in the library?

    If a library is designed with this purpose in mind, that is trivial as
    you just pointed out. All collection types in the library would
    implement the required interface. End of story.

    (But I note
    that if you think it /shouldn't/ be done, I won't expect you to show me
    how.)

    That is not a language question. It is a question of the library design.
    What if the library did not follow the desired design? That would be a
    language question and Ada offers some means, but not enough from my
    point of view due to the limitation of its type system.

    Should the language allow adding
    ad-hoc interfaces to existing types. Yes, and this is possible in Ada in
    some very uncomfortable AKA cumbersome way, which is why "finding maximum" >> is not a worthy abstraction in Ada.

    I suspected one might have to extend the interfaces.

    You cannot in a strongly typed language without breaking too much
    things. You must create another type related to the old one and
    implementing the new interface (superclass). That would do the trick.
    Ada cannot this, so you go for the poor man's substitute: a mix-in. I.e.
    you create a new type that references an object of the old type. E.g.
    see array cursors example in my earlier post.

    What closure is required for a function composition? There is no
    environment to "close over".

    In Ada a function can use anything visible at its declaration point and at >> the location of its body. You can even declare a function inside a
    recursively called function and let it see local variables of each
    recursive call, in effect having an infinite set of functions.

    At the point where I want Period.Element I can write the (almost)
    one-line function that takes a Cursor and returns Period(Element(C))
    entirely mechanically. Can't the compiler do that?

    No.

    (Ada indeed composes functions in some limited number of cases, e.g. an explicit type conversion of [in] out arguments. But these are predefined.)

    Note I'm not asking if it /should/ (it may not be "Ada-like" to do
    that). I'm just curious if there really is a technical reason it can't
    be done.

    Actually compositions might be useful in many cases and adapting
    interfaces is one of them.

    That's a lot just to use something that is supposed to be reusable.

    [rant on]
    An Ada programmer would just write a loop.

    Yes, that's fine. Different languages have different objectives. Just
    write the empty range test and the loop you need for each kind of
    collection.

    You can loop in Ada over empty ranges, no problem.

    That was definitely the way things were done in the 80s.

    Yes, before the Dark Ages of Computing...

    It only occurred to me after writing the non-generic solution. I
    remember Ada as being something of a pioneer in it's attempt to provide
    generic solutions, so I wondered how far things had come. I don't think >>> something really widely reusable is possible in this case.

    As I said you think in a wrong direction of abstracting the language
    "finding maximum" rather than the problem space, e.g. generalization to
    other bases, other mathematical structures etc.

    Generalising to an arbitrary base is local to the function that finds
    the answer for one element. It's an entirely separate axis of
    generalisation to that of where the elements come from.

    It's interesting to me that you consider one simply wrong and the other natural.

    Because one is a software design artifact and another is the result of
    problem space analysis.

    In some languages the "wrong" one does not even merit
    consideration as it's just there for free.

    Being a part of design it has all possible merits to consider and then
    reject it. That is in the position of a puzzle solver. Now in the
    position of a library designer, the Ada standard library has an
    [informal] interface that supports what you wanted:

    1. Cursor
    2. Key at the cursor
    3. Element at the cursor
    4. Iterate procedure

    So, for the Ada standard library it might look like this:

    generic
    type Container_Type (<>) is limited private;
    type Element_Type is private;
    type Key_Type is private;
    type Cursor_Type is private;
    with function "<" (Left, Right : Element_Type) return Boolean is <>;
    with function Key (Position : Cursor_Type) return Key_Type is <>;
    with function Element
    ( Position : Cursor_Type
    ) return Element_Type is <>;
    with procedure Iterate
    ( Container : Container_Type;
    Process : not null access procedure
    (Position : Cursor_Type)
    ) is <>;
    function Generic_Container_Maximum_At (Container : Container_Type)
    return Key_Type;

    function Generic_Container_Maximum_At (Container : Container_Type)
    return Key_Type is
    Found : Boolean := False;
    Max : Element_Type;
    Result : Key_Type;
    procedure Walker (Position : Cursor_Type) is
    begin
    if Found then
    if Max < Element (Position) then
    Result := Key (Position);
    Max := Element (Position);
    end if;
    else
    Result := Key (Position);
    Max := Element (Position);
    Found := True;
    end if;
    end Walker;
    begin
    Iterate (Container, Walker'Access);
    if Found then
    return Result;
    else
    raise Constraint_Error with "Empty container";
    end if;
    end Generic_Container_Maximum_At;

    Instantiation:

    package Integer_Maps is
    new Ada.Containers.Ordered_Maps (Integer, Integer);
    use Integer_Maps;
    function Integer_Map_Max is
    new Generic_Container_Maximum_At (Map, Integer, Integer, Cursor);

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to G.B. on Sat Sep 9 22:04:34 2023
    "G.B." <bauhaus@notmyhomepage.invalid> writes:

    On 08.09.23 23:02, Ben Bacarisse wrote:
    "G.B." <bauhaus@notmyhomepage.invalid> writes:

    On 07.09.23 01:32, Ben Bacarisse wrote:


    A fix (though it's not really ideal) would be to use function
    composition here (inventing . as the composition operator):

    Hm. A stateful, composed function that needs to be applied
    in a certain way. Is that so different from calling interface
    subprograms of a certain type?
    There was nothing stateful (as I understand the term) in either function
    being composed.

    The "apparatus" that the computation needs in order to remember
    "max so far" looks like part of its state to me.

    The "max so far" function is not being composed.

    Somehow
    "the function" needs to operate this state and evaluate it.
    Extend this to:
    - find the maximum of [the maxima of] these n collections
    - find the maximum in this stream at 10 seconds from now.

    Is it possible, or practical, to define a pure function so that
    calling it will remember the needed information, n >= 0
    being arbitrary?

    I am not sure how the discussion got here. Ada is an imperative
    language so of course one would use "running" state to calculate a
    maximum. The max_of_F_over_X function just loops like any other loop
    from First_Of(X) to Last_Of(X) calculating F(This(X)), comparing that
    with Max_So_Far.

    These are invented names, of course, because I don't know how it should
    be done, but the idea is plain imperative code. In fact, it's possible
    that Ada has some entirely different syntax for this kind of imperative
    loop.

    The "fix" to use a composed function was because one proposed solution
    found the maximum of Element(C) (where C was a cursor) because Element
    was passed as F, but that of course is not what was wanted. To find the maximum of F I speculated that one could pass F.Element.

    So, does type composition help?
    My turn to guess now: you are not being serious? I see no connection to
    monads or type composition.

    In the following sense:
    There is an object of type So_Far that can remember
    objects of any type T, them coming from collections
    of type C-of-T.

    Given the above confusion about what is being composed, I can see the connection with monads. But there is no reason to use the concept of a
    monad in a language with modifiable state. The maximum should be found
    as in the posted code with a simple loop.

    I'm not sure if the new Ada.Iterator_Interfaces (LRM 5.5.1)
    could solve this, also because I really don't know that yet.
    But it looks like I'd need instances of specific containers
    for instantiation. (That being consistent with Ada's approach
    to the STL, I think.)

    Thanks for the pointer. I am not sure I have time to look in detail,
    but it looks interesting.

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to Dmitry A. Kazakov on Sun Sep 10 02:20:20 2023
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-09 02:25, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    [rant on]
    An Ada programmer would just write a loop.
    Yes, that's fine. Different languages have different objectives. Just
    write the empty range test and the loop you need for each kind of
    collection.

    You can loop in Ada over empty ranges, no problem.

    Yes, but the problem in hand (maximum of F over X) should raise an error
    on an empty X. I know there are other options, but you chose to
    raise an error so that's the design I was talking about.

    That was definitely the way things were done in the 80s.

    Yes, before the Dark Ages of Computing...

    Eh? There have been repeated updates to the Ada language. Are they
    taking Ada into the dark ages? If so, what was the golden age of Ada
    when its design was perfect for numerical algorithms?

    As I said you think in a wrong direction of abstracting the language
    "finding maximum" rather than the problem space, e.g. generalization to
    other bases, other mathematical structures etc.
    Generalising to an arbitrary base is local to the function that finds
    the answer for one element. It's an entirely separate axis of
    generalisation to that of where the elements come from.
    It's interesting to me that you consider one simply wrong and the other
    natural.

    Because one is a software design artifact and another is the result of problem space analysis.

    Which one the wrong one?

    In some languages the "wrong" one does not even merit
    consideration as it's just there for free.

    Being a part of design it has all possible merits to consider and then
    reject it. That is in the position of a puzzle solver. Now in the position
    of a library designer, the Ada standard library has an [informal] interface that supports what you wanted:

    Well, there has been some confusion over that, but from what I
    understand of the code below, adding in a function to maximise would be
    simple.

    1. Cursor
    2. Key at the cursor
    3. Element at the cursor
    4. Iterate procedure

    So, for the Ada standard library it might look like this:

    generic
    type Container_Type (<>) is limited private;
    type Element_Type is private;
    type Key_Type is private;
    type Cursor_Type is private;
    with function "<" (Left, Right : Element_Type) return Boolean is <>;
    with function Key (Position : Cursor_Type) return Key_Type is <>;
    with function Element
    ( Position : Cursor_Type
    ) return Element_Type is <>;
    with procedure Iterate
    ( Container : Container_Type;
    Process : not null access procedure
    (Position : Cursor_Type)
    ) is <>;
    function Generic_Container_Maximum_At (Container : Container_Type)
    return Key_Type;

    function Generic_Container_Maximum_At (Container : Container_Type)
    return Key_Type is
    Found : Boolean := False;
    Max : Element_Type;
    Result : Key_Type;
    procedure Walker (Position : Cursor_Type) is
    begin
    if Found then
    if Max < Element (Position) then
    Result := Key (Position);
    Max := Element (Position);
    end if;
    else
    Result := Key (Position);
    Max := Element (Position);
    Found := True;
    end if;
    end Walker;
    begin
    Iterate (Container, Walker'Access);
    if Found then
    return Result;
    else
    raise Constraint_Error with "Empty container";
    end if;
    end Generic_Container_Maximum_At;

    Instantiation:

    package Integer_Maps is
    new Ada.Containers.Ordered_Maps (Integer, Integer);
    use Integer_Maps;
    function Integer_Map_Max is
    new Generic_Container_Maximum_At (Map, Integer, Integer, Cursor);

    This is probably the closest we can get to a universal solution.
    Vectors don't have a Key function but I am sure I could find out what
    should be provided there.

    Thanks.

    I agree that is does not feel worth it. Just write the loop our each time.

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to Ben Bacarisse on Sun Sep 10 10:46:04 2023
    On 2023-09-10 03:20, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-09 02:25, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    [rant on]
    An Ada programmer would just write a loop.
    Yes, that's fine. Different languages have different objectives. Just
    write the empty range test and the loop you need for each kind of
    collection.

    You can loop in Ada over empty ranges, no problem.

    Yes, but the problem in hand (maximum of F over X) should raise an error
    on an empty X. I know there are other options, but you chose to
    raise an error so that's the design I was talking about.

    It can be done by a Boolean flag.

    That was definitely the way things were done in the 80s.

    Yes, before the Dark Ages of Computing...

    Eh? There have been repeated updates to the Ada language. Are they
    taking Ada into the dark ages? If so, what was the golden age of Ada
    when its design was perfect for numerical algorithms?

    I meant the state of computing as a whole.

    (Ada is a niche language and "hordes of barbarians" largely missed its existence... (:-))

    As I said you think in a wrong direction of abstracting the language
    "finding maximum" rather than the problem space, e.g. generalization to >>>> other bases, other mathematical structures etc.
    Generalising to an arbitrary base is local to the function that finds
    the answer for one element. It's an entirely separate axis of
    generalisation to that of where the elements come from.
    It's interesting to me that you consider one simply wrong and the other
    natural.

    Because one is a software design artifact and another is the result of
    problem space analysis.

    Which one the wrong one?

    None automatically is. The point is avoiding overdesigning a numeric puzzle.

    [...]
    This is probably the closest we can get to a universal solution.
    Vectors don't have a Key function but I am sure I could find out what
    should be provided there.

    Vector has To_Index for Key.

    In general, note that Ada does not require you to use any library. I
    personally dislike cursors in particular because of their "functional"
    style. I prefer plain element position and loop iteration of ordered structures. A container library based on this paradigm would use other
    generic abstraction.

    Furthermore, I prefer dynamic polymorphism of tagged types over
    parametric one of generics. Therefore to me Maximum_At should rather be
    a class-wide or primitive operation than a generic.

    In Ada you have freedom to choose your way, which also massively reduces universality of any abstraction, which will never apply universally.

    I would like to have means to deal with this problem by means of ad-hoc supertypes, but that will never happen due to lack of interest in
    reworking the language type system and because in "Dark Ages" there is virtually no research on fundamental language construction topics.

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to G.B. on Sun Sep 10 11:11:18 2023
    On 2023-09-09 10:13, G.B. wrote:

    The "apparatus" that the computation needs in order to remember
    "max so far" looks like part of its state to me. Somehow
    "the function" needs to operate this state and evaluate it.

    You can hide explicit state using recursion.

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to Dmitry A. Kazakov on Sun Sep 10 20:22:54 2023
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-10 03:20, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-09 02:25, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    As I said you think in a wrong direction of abstracting the language >>>>> "finding maximum" rather than the problem space, e.g. generalization to >>>>> other bases, other mathematical structures etc.
    Generalising to an arbitrary base is local to the function that finds
    the answer for one element. It's an entirely separate axis of
    generalisation to that of where the elements come from.
    It's interesting to me that you consider one simply wrong and the other >>>> natural.

    Because one is a software design artifact and another is the result of
    problem space analysis.
    Which one the wrong one?

    None automatically is. The point is avoiding overdesigning a numeric
    puzzle.

    Ah, I thought your criticise was intended to be general -- that
    "abstracting the language 'finding maximum' rather than the problem
    space" was always wrong, but it seems you meant only in the case of a
    puzzle like this. Numeric puzzles like this should only be generalised
    in a few "approved" directions?

    Obviously I disagree. I would probably not bother doing this sort of
    puzzle if it did not spark thoughts that go well beyond getting the
    answer and a few obvious variation like using a different base.

    Because I am interested in programming languages in general I always
    solve such puzzles in more than one language so I can see how well they
    express the algorithms involved.

    Since prime numbers are crucial here, I had already tried a couple of
    prime sieves in one of my solutions. In that Ada solution, I would
    probably have to store the primes somewhere and maximise over that.
    That's what got me thinking about a general "maximise F over X" function because if Ada had a simple way to do that, I could try various ways to
    write the sieve -- the primes might end up in an array, a set or a map,
    and it would make no difference to the rest of the code.

    But the conclusion seems to be that maximising over any container is
    just too simple to be worth making it a reusable component in Ada. And
    even then it would not (as far as I can tell) work for native arrays.

    [...]
    This is probably the closest we can get to a universal solution.
    Vectors don't have a Key function but I am sure I could find out what
    should be provided there.

    Vector has To_Index for Key.

    In general, note that Ada does not require you to use any library. I personally dislike cursors in particular because of their "functional"
    style. I prefer plain element position and loop iteration of ordered structures. A container library based on this paradigm would use other generic abstraction.

    Furthermore, I prefer dynamic polymorphism of tagged types over parametric one of generics. Therefore to me Maximum_At should rather be a class-wide
    or primitive operation than a generic.

    I was looking for whatever design you thought best, since you know Ada infinitely better that I do. It would be a shame if something I said
    has ended up causing you to propose solutions you don't think are the
    best ones for this example.

    In Ada you have freedom to choose your way, which also massively reduces universality of any abstraction, which will never apply universally.

    That's a strange remark. You have to do things the Ada way. The
    freedom is only in choosing how to combine the specific tools in Ada's
    toolbox, and Ada also constrains how the tools can be combined. This is
    true for any programming language. None of then give you the freedom
    choose your way unless your way already aligns with what it permitted!

    I would like to have means to deal with this problem by means of ad-hoc supertypes, but that will never happen due to lack of interest in reworking the language type system and because in "Dark Ages" there is virtually no research on fundamental language construction topics.

    I don't believe that to be the case. I can believe that there is little research into overhauling Ada's type system, but not in general.

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to Ben Bacarisse on Mon Sep 11 08:53:12 2023
    On 2023-09-10 21:22, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-10 03:20, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-09 02:25, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    As I said you think in a wrong direction of abstracting the language >>>>>> "finding maximum" rather than the problem space, e.g. generalization to >>>>>> other bases, other mathematical structures etc.
    Generalising to an arbitrary base is local to the function that finds >>>>> the answer for one element. It's an entirely separate axis of
    generalisation to that of where the elements come from.
    It's interesting to me that you consider one simply wrong and the other >>>>> natural.

    Because one is a software design artifact and another is the result of >>>> problem space analysis.
    Which one the wrong one?

    None automatically is. The point is avoiding overdesigning a numeric
    puzzle.

    Ah, I thought your criticise was intended to be general -- that
    "abstracting the language 'finding maximum' rather than the problem
    space" was always wrong, but it seems you meant only in the case of a
    puzzle like this. Numeric puzzles like this should only be generalised
    in a few "approved" directions?

    Yes, in the direction of numeric problem space. Universal finding
    maximum is another problem space, e.g. a container library design etc.

    Since prime numbers are crucial here, I had already tried a couple of
    prime sieves in one of my solutions. In that Ada solution, I would
    probably have to store the primes somewhere and maximise over that.
    That's what got me thinking about a general "maximise F over X" function because if Ada had a simple way to do that, I could try various ways to
    write the sieve -- the primes might end up in an array, a set or a map,
    and it would make no difference to the rest of the code.

    And this is exactly wrong. You should think about whether storing
    represents an issue, e.g. in terms of performance and/or space. If it
    does you should consider suitable implementation of storage that
    provides required overall performance of needed operations, like
    insertion, search, cleaning up etc.

    But the conclusion seems to be that maximising over any container is
    just too simple to be worth making it a reusable component in Ada. And
    even then it would not (as far as I can tell) work for native arrays.

    You do not need *any* container. You need a container, just one.

    [...]
    This is probably the closest we can get to a universal solution.
    Vectors don't have a Key function but I am sure I could find out what
    should be provided there.

    Vector has To_Index for Key.

    In general, note that Ada does not require you to use any library. I
    personally dislike cursors in particular because of their "functional"
    style. I prefer plain element position and loop iteration of ordered
    structures. A container library based on this paradigm would use other
    generic abstraction.

    Furthermore, I prefer dynamic polymorphism of tagged types over parametric >> one of generics. Therefore to me Maximum_At should rather be a class-wide
    or primitive operation than a generic.

    I was looking for whatever design you thought best, since you know Ada infinitely better that I do.

    The best design is plain loop.

    It would be a shame if something I said
    has ended up causing you to propose solutions you don't think are the
    best ones for this example.

    My understanding was that you wanted to see how to use the Ada standard
    library containers with generics.

    Generic programming in Ada (programming in terms of sets of types) is a
    huge, almost infinite topic. One should be rather specific.

    In Ada you have freedom to choose your way, which also massively reduces
    universality of any abstraction, which will never apply universally.

    That's a strange remark. You have to do things the Ada way. The
    freedom is only in choosing how to combine the specific tools in Ada's toolbox, and Ada also constrains how the tools can be combined.

    There are more than one way to skin a cat in Ada. You can choose one
    drawer in the Ada toolbox and feel comfortable with what it provides all
    your life.

    "Ada way" among Ada users rather refers to an approach to software
    engineering in general. Like upfront specification, separation and
    careful design of interfaces, modular design, problem space driven
    choice of types, earliest possible error detection etc.

    I would like to have means to deal with this problem by means of ad-hoc
    supertypes, but that will never happen due to lack of interest in reworking >> the language type system and because in "Dark Ages" there is virtually no
    research on fundamental language construction topics.

    I don't believe that to be the case. I can believe that there is little research into overhauling Ada's type system, but not in general.

    I am not aware of any substantial contributions since Cardelli etc.
    Recently designed languages represent a pitiful mess of old wrong ideas
    in an ongoing competition to create something more flawed than K&R C...

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to Dmitry A. Kazakov on Mon Sep 11 17:13:30 2023
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-10 21:22, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-10 03:20, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-09 02:25, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    As I said you think in a wrong direction of abstracting the language >>>>>>> "finding maximum" rather than the problem space, e.g. generalization to >>>>>>> other bases, other mathematical structures etc.
    Generalising to an arbitrary base is local to the function that finds >>>>>> the answer for one element. It's an entirely separate axis of
    generalisation to that of where the elements come from.
    It's interesting to me that you consider one simply wrong and the other >>>>>> natural.

    Because one is a software design artifact and another is the result of >>>>> problem space analysis.
    Which one the wrong one?

    None automatically is. The point is avoiding overdesigning a numeric
    puzzle.
    Ah, I thought your criticise was intended to be general -- that
    "abstracting the language 'finding maximum' rather than the problem
    space" was always wrong, but it seems you meant only in the case of a
    puzzle like this. Numeric puzzles like this should only be generalised
    in a few "approved" directions?

    Yes, in the direction of numeric problem space. Universal finding maximum
    is another problem space, e.g. a container library design etc.

    Noted! I will try to guess what generalisations you might approve of
    in future :-)

    Since prime numbers are crucial here, I had already tried a couple of
    prime sieves in one of my solutions. In that Ada solution, I would
    probably have to store the primes somewhere and maximise over that.
    That's what got me thinking about a general "maximise F over X" function
    because if Ada had a simple way to do that, I could try various ways to
    write the sieve -- the primes might end up in an array, a set or a map,
    and it would make no difference to the rest of the code.

    And this is exactly wrong.

    In Ada. It works well in some other languages for reasons I'll explain
    just below.

    You should think about whether storing
    represents an issue, e.g. in terms of performance and/or space. If it does you should consider suitable implementation of storage that provides
    required overall performance of needed operations, like insertion, search, cleaning up etc.

    Yes, in Ada. Since I can't use universal algorithms, it pays to decide
    all this first because changes will be costly. But in some other
    languages I can try various schemes and measure or profile to see what time/space trade-offs there are between different designs. This is
    easiest when I don't have to worry about all the changes that simply
    switching from, say, a list to an array will incur.

    But the conclusion seems to be that maximising over any container is
    just too simple to be worth making it a reusable component in Ada. And
    even then it would not (as far as I can tell) work for native arrays.

    You do not need *any* container. You need a container, just one.

    Yes, in Ada. The cost of changing a design is going to be
    non-negligible, so we must make sure you get it right before too much
    code is written.

    [...]
    This is probably the closest we can get to a universal solution.
    Vectors don't have a Key function but I am sure I could find out what
    should be provided there.

    Vector has To_Index for Key.

    In general, note that Ada does not require you to use any library. I
    personally dislike cursors in particular because of their "functional"
    style. I prefer plain element position and loop iteration of ordered
    structures. A container library based on this paradigm would use other
    generic abstraction.

    Furthermore, I prefer dynamic polymorphism of tagged types over parametric >>> one of generics. Therefore to me Maximum_At should rather be a class-wide >>> or primitive operation than a generic.
    I was looking for whatever design you thought best, since you know Ada
    infinitely better that I do.

    The best design is plain loop.

    Yes, in Ada.

    It would be a shame if something I said
    has ended up causing you to propose solutions you don't think are the
    best ones for this example.

    My understanding was that you wanted to see how to use the Ada standard library containers with generics.

    Well that's what it turned out to be. At first I did not know that
    built-in types like arrays can't be covered in the same way.

    Generic programming in Ada (programming in terms of sets of types) is a
    huge, almost infinite topic. One should be rather specific.

    Sorry. I was hoping that generalising from a range to an array or some
    other container would not be the huge topic it turned out to be.

    In Ada you have freedom to choose your way, which also massively reduces >>> universality of any abstraction, which will never apply universally.
    That's a strange remark. You have to do things the Ada way. The
    freedom is only in choosing how to combine the specific tools in Ada's
    toolbox, and Ada also constrains how the tools can be combined.

    There are more than one way to skin a cat in Ada. You can choose one drawer in the Ada toolbox and feel comfortable with what it provides all your
    life.

    "Ada way" among Ada users rather refers to an approach to software engineering in general. Like upfront specification, separation and careful design of interfaces, modular design, problem space driven choice of types, earliest possible error detection etc.

    Yes, I remember the 80s! It's rare to have specifications that don't
    change these days. And general remarks like "problem space driven
    choice of types" apply to all languages. What matters is what types the language offers, and what the interfaces to those types are.

    I would like to have means to deal with this problem by means of ad-hoc
    supertypes, but that will never happen due to lack of interest in reworking >>> the language type system and because in "Dark Ages" there is virtually no >>> research on fundamental language construction topics.
    I don't believe that to be the case. I can believe that there is little
    research into overhauling Ada's type system, but not in general.

    I am not aware of any substantial contributions since Cardelli
    etc. Recently designed languages represent a pitiful mess of old wrong
    ideas in an ongoing competition to create something more flawed than K&R
    C...

    Forgive me, but that does not appear to be a well-informed option. You
    may be bang up to date as far as research into programming language type systems is concerned, but that reply does no read as if it were written
    by someone who is.

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to Ben Bacarisse on Tue Sep 12 09:17:56 2023
    On 2023-09-11 18:13, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-10 21:22, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    You should think about whether storing
    represents an issue, e.g. in terms of performance and/or space. If it does >> you should consider suitable implementation of storage that provides
    required overall performance of needed operations, like insertion, search, >> cleaning up etc.

    Yes, in Ada. Since I can't use universal algorithms, it pays to decide
    all this first because changes will be costly.

    There are no universally applicable algorithms.

    But in some other
    languages I can try various schemes and measure or profile to see what time/space trade-offs there are between different designs.

    So you can in Ada.

    This is
    easiest when I don't have to worry about all the changes that simply switching from, say, a list to an array will incur.

    Measuring performance is not a simple task. Switching from the visitor
    pattern to loop is your least problem.

    But the conclusion seems to be that maximising over any container is
    just too simple to be worth making it a reusable component in Ada. And
    even then it would not (as far as I can tell) work for native arrays.

    You do not need *any* container. You need a container, just one.

    Yes, in Ada. The cost of changing a design is going to be
    non-negligible, so we must make sure you get it right before too much
    code is written.

    Right, because in that case you would have some non-trivial issue. So it
    would take much more efforts than merely calling a different function.
    There is an inherent difference between dealing with real size and
    complexity projects and hobby examples like this puzzle. The overhead
    you get from Ada pays off in programming en large. That was intentional language design.

    It would be a shame if something I said
    has ended up causing you to propose solutions you don't think are the
    best ones for this example.

    My understanding was that you wanted to see how to use the Ada standard
    library containers with generics.

    Well that's what it turned out to be. At first I did not know that
    built-in types like arrays can't be covered in the same way.

    I know no language where primitive built-in types may have classes. That
    is the major problem with type systems that they have first, second and
    third class citizens. Ada arrays (and fixed strings) are in a different
    basket than containers.

    Generic programming in Ada (programming in terms of sets of types) is a
    huge, almost infinite topic. One should be rather specific.

    Sorry. I was hoping that generalising from a range to an array or some
    other container would not be the huge topic it turned out to be.

    Unfortunately it is, because nobody knows how to design a type system
    where proper arrays, that is one you could pass to a system library
    function written in C, can be dealt with in the same manner as a
    container in some polymorphic body. A mainstream choice is not to have
    proper arrays in the language at all. Then, logically, just forget that
    they exist in Ada. Problem solved!

    In Ada you have freedom to choose your way, which also massively reduces >>>> universality of any abstraction, which will never apply universally.
    That's a strange remark. You have to do things the Ada way. The
    freedom is only in choosing how to combine the specific tools in Ada's
    toolbox, and Ada also constrains how the tools can be combined.

    There are more than one way to skin a cat in Ada. You can choose one drawer >> in the Ada toolbox and feel comfortable with what it provides all your
    life.

    "Ada way" among Ada users rather refers to an approach to software
    engineering in general. Like upfront specification, separation and careful >> design of interfaces, modular design, problem space driven choice of types, >> earliest possible error detection etc.

    Yes, I remember the 80s! It's rare to have specifications that don't
    change these days.

    I remember a book on structured programming from 80's describing exactly
    the way programs are written today as an example how projects are doomed
    to fail. As I said, Dark Ages.

    And general remarks like "problem space driven
    choice of types" apply to all languages.

    In most languages there is no choice because all scalar types are
    predefined.

    What matters is what types the
    language offers, and what the interfaces to those types are.

    That does not matter at all. Matters the type algebra by which
    programmer can create types suitable to model the problem space entities.

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to Dmitry A. Kazakov on Wed Sep 13 13:24:44 2023
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-11 18:13, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    You should think about whether storing
    represents an issue, e.g. in terms of performance and/or space. If it does >>> you should consider suitable implementation of storage that provides
    required overall performance of needed operations, like insertion, search, >>> cleaning up etc.

    Yes, in Ada. Since I can't use universal algorithms, it pays to decide
    all this first because changes will be costly.

    There are no universally applicable algorithms.

    This may be just a case where we are using terms to refer to different
    things. I find it hard to believe you don't know what I am referring to
    since we've had a productive exchange examining an example in detail,
    but I can agree it's not a good term. I simply could not come up with a
    better one on the fly.

    So I'll re-phrase it avoiding the disputed term: simple fibledychops are
    not available to the Ada programmer, but they are available in some
    other languages. I suspect you are not interested in what simple
    fibledychops are, since their absence from Ada means they are not of any importance (and may even be, in your opinion, detrimental to writing
    good programs). If you really want to know what a fibledychop is, I can
    have a go at saying more about what they it, but would that be
    worthwhile? I think you are sure they are a bad idea already.

    My understanding was that you wanted to see how to use the Ada standard
    library containers with generics.

    Well that's what it turned out to be. At first I did not know that
    built-in types like arrays can't be covered in the same way.

    I know no language where primitive built-in types may have classes.

    Haskell's type classes are very nice -- every type belongs to one or
    more classes that determine the permitted operations. And in some
    languages there are essentially no "built-in" types. In ML for example,
    the interface to arrays is defined in ML so they can support a universal
    set of operations shared with many other types, but they are usually implemented by the run-time environment for speed.

    What matters is what types the
    language offers, and what the interfaces to those types are.

    That does not matter at all. Matters the type algebra by which programmer
    can create types suitable to model the problem space entities.

    Yes, but... First, almost every language comes with some predefined
    types. If the problem space needs fast indexed access to a set of
    entities, we don't usually have to define our own arrays or vectors.
    It's so often needed that we expect something to be provided, so what
    types the language offers /does/ matter. Secondly, the problem space
    has two components -- data and actions on that data. I suspect by
    "problem space entities" you mean just the data because that what Ada
    focuses on. But programming languages can offer tool that help to model
    the actions in the problem space as well.

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Dmitry A. Kazakov@21:1/5 to Ben Bacarisse on Thu Sep 14 08:33:35 2023
    On 2023-09-13 14:24, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    On 2023-09-11 18:13, Ben Bacarisse wrote:
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    You should think about whether storing
    represents an issue, e.g. in terms of performance and/or space. If it does >>>> you should consider suitable implementation of storage that provides
    required overall performance of needed operations, like insertion, search, >>>> cleaning up etc.

    Yes, in Ada. Since I can't use universal algorithms, it pays to decide
    all this first because changes will be costly.

    There are no universally applicable algorithms.

    This may be just a case where we are using terms to refer to different things. I find it hard to believe you don't know what I am referring to since we've had a productive exchange examining an example in detail,
    but I can agree it's not a good term. I simply could not come up with a better one on the fly.

    So I'll re-phrase it avoiding the disputed term: simple fibledychops are
    not available to the Ada programmer, but they are available in some
    other languages. I suspect you are not interested in what simple fibledychops are, since their absence from Ada means they are not of any importance (and may even be, in your opinion, detrimental to writing
    good programs). If you really want to know what a fibledychop is, I can
    have a go at saying more about what they it, but would that be
    worthwhile? I think you are sure they are a bad idea already.

    Each language feature has a purpose. Roughly it is called language
    paradigm: how routine programming activities are approached when using
    the language. Ada's paradigm is different from what you expect. E.g.
    sunroof might be a simple car feature, but a submarine user would not be impressed.

    My understanding was that you wanted to see how to use the Ada standard >>>> library containers with generics.

    Well that's what it turned out to be. At first I did not know that
    built-in types like arrays can't be covered in the same way.

    I know no language where primitive built-in types may have classes.

    Haskell's type classes are very nice -- every type belongs to one or
    more classes that determine the permitted operations.

    No difference to Ada. Integer belongs to an integer class and there is a
    formal generic type for the class members. The problem I am talking
    about is that there is no run-time objects of and no non-integer type
    can be put in that class.

    In ML for example,
    the interface to arrays is defined in ML so they can support a universal
    set of operations shared with many other types, but they are usually implemented by the run-time environment for speed.

    Can I take integer type, derive a new *integer* type from it such that
    it would also implement an array interface? So that I could access
    integer decimal digits? Or use your "fibledychops" with on it?

    This is impossible in Ada. Which is in particular why Ada ordered
    containers do not implement array interface. They simply cannot.

    Ada has a generic array interface declared as

    generic
    type Index_Type is ...
    type Element_Type is ...
    type Array_Type is array (Index_Type range <>) of Element_Type;

    but even that is not implementable by anything except by a proper array.

    Yes, there is an ugly iterator hack Georg mentioned in another thread.
    The hack allows containers to *look* like arrays in syntax, e.g. you can
    loop and index a container this way.

    This is possibly what you meant referencing ML. But I do not know ML.

    What matters is what types the
    language offers, and what the interfaces to those types are.

    That does not matter at all. Matters the type algebra by which programmer
    can create types suitable to model the problem space entities.

    Yes, but... First, almost every language comes with some predefined
    types. If the problem space needs fast indexed access to a set of
    entities, we don't usually have to define our own arrays or vectors.

    Index and element types always same?

    When I derive a new type from the array element type, would an array of
    such elements related to an array of base element type? Can I control
    the decision? Can I have an array of elements from both element types?
    How such arrays are related to the specific element type arrays. Then
    add the index types hierarchy to the picture...

    You would say: uninterested. So I am in "fibledychops"... (:-))

    Secondly, the problem space
    has two components -- data and actions on that data. I suspect by
    "problem space entities" you mean just the data because that what Ada
    focuses on.

    No, in Ada it is both. You can add "free functions" as you wish,
    anytime, anywhere. It is the classes and their primitive operations (AKA methods) that pose problems.

    --
    Regards,
    Dmitry A. Kazakov
    http://www.dmitry-kazakov.de

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Ben Bacarisse@21:1/5 to All on Thu Sep 14 15:30:36 2023
    "Dmitry A. Kazakov" <mailbox@dmitry-kazakov.de> writes:

    ...

    I feel it's time to draw this to a close, so I'll just say thank you for
    your time. I didn't want you to think I hadn't read your post, but I
    think we're starting to repeat ourselves. The only new technical
    matters were some questions about ML's type system and that would be
    getting very far off-topic for this group.

    I always enjoy getting a different perspective on such topics. I hope
    you do to.

    --
    Ben.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From CSYH (QAQ)@21:1/5 to Francesc Rocher on Fri Sep 15 02:07:40 2023
    On Thursday, September 7, 2023 at 3:31:12 PM UTC+8, Francesc Rocher wrote:
    El dia dilluns, 4 de setembre de 2023 a les 11:19:53 UTC+2, CSYH (QAQ) va escriure:
    I am new to Ada, I know is there a good way to start this program?
    thanks
    https://projecteuler.net/problem=26
    Hi CSHY,

    Please take a look at my Euler tools repository, https://github.com/rocher/euler_tools (not the best math lib you'll find, I know).
    I used this library tools to solve problem 26 here: https://github.com/rocher/alice-project_euler-rocher
    Let me know what you think.
    sorry for reply so late. I just do not know how to install the lib to my GNAT.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From comp.lang.ada@21:1/5 to All on Tue Sep 19 00:59:56 2023
    Please take a look at my Euler tools repository, https://github.com/rocher/euler_tools (not the best math lib you'll find, I know).
    I used this library tools to solve problem 26 here: https://github.com/rocher/alice-project_euler-rocher
    Let me know what you think.

    sorry for reply so late. I just do not know how to install the lib to my GNAT.

    First of all, you need to install Alire on your system: https://alire.ada.dev Second, simply follow these steps:

    1. Clone euler_tools: "git clone https://github.com/rocher/euler_tools"
    2. Enter examples directory: "cd euler_tools/examples"
    3. Build examples: "alr build"

    Included examples are problems 26 and 29 (discussed in another thread).

    If you'd like to discuss any other Project Euler problem, I have solved from 1 to 30 (at the moment).
    It'll be a pleasure to review/discuss any other problem.

    BR
    ---
    Francesc Rocher

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)