Jump to page: 1 26  
Page
Thread overview
Some questions and suggestions, and the future of D
(part 2) Some questions and suggestions, and the future of D
Jul 11, 2002
C.R.Chafer
Jul 12, 2002
Sean L. Palmer
Jul 11, 2002
anderson
Jul 11, 2002
Andrey Tarantsov
Jul 11, 2002
anderson
Jul 11, 2002
Andrey Tarantsov
Jul 12, 2002
anderson
Jul 20, 2002
Walter
Jul 20, 2002
Sean L. Palmer
Jul 20, 2002
Walter
Jul 22, 2002
Russ Lewis
Jul 22, 2002
Pavel Minayev
Jul 22, 2002
anderson
Jul 22, 2002
anderson
Jul 23, 2002
Sandor Hojtsy
Jul 22, 2002
Jonathan Andrew
Jul 22, 2002
Jonathan Andrew
Jul 13, 2002
OddesE
Jul 11, 2002
C.R.Chafer
Jul 11, 2002
andy
Jul 12, 2002
Andrey Tarantsov
Jul 12, 2002
Sean L. Palmer
Jul 20, 2002
Walter
Jul 20, 2002
Sean L. Palmer
Jul 20, 2002
Walter
Jul 11, 2002
Toyotomi
Jul 11, 2002
Toyotomi
Jul 13, 2002
OddesE
Jul 15, 2002
Toyotomi
Jul 16, 2002
OddesE
Jul 16, 2002
anderson
Jul 20, 2002
Walter
Jul 21, 2002
Steven Shaw
Jul 21, 2002
Walter
Jul 21, 2002
Steven Shaw
Jul 21, 2002
Pavel Minayev
Jul 21, 2002
Walter
Jul 22, 2002
Steven Shaw
Jul 22, 2002
Walter
Jul 23, 2002
Walter
Jul 25, 2002
anderson
Jul 12, 2002
Sean L. Palmer
Jul 12, 2002
anderson
Jul 13, 2002
OddesE
Jul 13, 2002
Sean L. Palmer
Jul 14, 2002
OddesE
Jul 14, 2002
anderson
Jul 14, 2002
Andrey Tarantsov
Jul 15, 2002
anderson
Jul 15, 2002
Sean L. Palmer
July 10, 2002
Hello everybody!

I've recently read D language spec. I can't say I like D, but I like the fact that you're crazy enough to invent your own languages and technologies - just like me. (No, I have no languages of my own.)

When I was a bit younger, I've tried to invent some languages too. Now I think that the language itself does not mean that much, am inventing new programming conception, use Delphi for my everyday programming and just love Ada. ;-) I want to share with you some thoughts about D.

D needs much much much more designing. Currently it is like Object Pascal: you've just put together everything you like in all other languages. I think it is really useful for everybody to learn Ada (by-the-by, a Pascal descendant), for that language has many samples of untraditional design.

There had been a language designed for everything at once: ease of programming, reading, typing, implementation, bug making. That's ALGOL. Do you want D to be a simple language (like Pascal) or a good language? I think D needs a small-to-medium redesign. I propose a discussion about the concepts of D.

First. You can't put everything into a language. Probably a language should contain a basic, general set of... em, capabilities (not sure it's a right word), and everything else should be defined using the language itself. Can you use a "naked" C++ for real development? No, you can't. You need some sort of programming environment. C standard library is the minimum environment. STL, MFC, C++ Builder's VCL add some useful features, but still I think that there's no usable programming environment for C++. But the best thing in C++ is that it allows you to create a very good one. Nobody did it, however. :-) But is integrating a fixed programming environment into the language a best thing? That depends on the goal of the language:

-> for small scripting languages for quick coding it is;
-> for real system languages I think it's not.

Specifically, I'm talking about dynamic arrays and garbage collection. While GC is probably OK to be integrated into the language (as for GC to be implemented using D, D must be low-level enough), but things like dynamic arrays should be implemented using standard classes. Why? Because if dynamic arrays can be implemented in D in a convenient and familiar way, then many other idioms (iterators, cursors, lists) can be implemented too.

Complex type. If you want to make every mathematical type a part of the language, I can tell you a lot of types that you've missed. :-) Complex must be a standard class! With source code written in plain D. So that when I need Vector or Tensor type, I will be able to implement it as easily as Complex is. (Or, wouldn't you please add Tensors to D? ;)

Why is D a descendant of C++, while it is much more like Pascal? The "spirit" of C++ is not a part of D, so I don't think it should look like C++. And, C++ is very self-contained language. I mean that adding something new to it is not quite easy and seamless.

Well, at last, syntax does not matter. Here I want to describe some concepts of my favourite language (Ada) that I think could be useful for D developers. Ada has two versions: Ada'83 and Ada'95 (the latter having OOP and a few other enhancements).

1. Types. In Ada, there exist types and *subtypes*. Types can derive from each other. Samples:

type Foo_Integer is range 0 .. 2 ** 32 - 1;
-- Foo_Integer is a completely new type. It is not compatible with anything
else.

type Bar_Integer is new Integer range -128 .. 127;
-- This is a *derived* type. It inherites all "primitive operations" of type
Integer, is compatible with
-- Integer if you use explicit conversion.
-- To call it a "signed byte" we want to add an "attribute declaration
clause":
for Bar_Integer'Size use 8; -- use 8 bits for this type

subtype Boz_Integer is Integer range 0 .. 255;
-- This is a subtype. It is like a synonim for other type, can be implicitly
converted back and forth.

Int : Integer := 7;
Foo : Foo_Integer;
Bar : Bar_Integer;
Boz : Boz_Integer;

Foo := Int; -- this is invalid. Integer and Foo_Integer are not compatible
Foo := Foo_Integer (Int); -- neither is this. They are really *incompatible*
;)
Bar := Int; -- Invalid! Thay are compatible, but they are different types.
Bar := Bar_Integer (Int); -- Okay
Boz := Int; -- Okay, as long as 0 <= Int <= 255. Else, Constraint_Error
exception is raised.
Int := Boz; -- Okay always.

Ada's types are the most wonderful and logic things I've ever seen. They provide a lot of useful features not found in any other language. I think you should consider this approach.

Somebody has asked for very long types here. They are made very easily:

type Int_256 is range 0 .. 2 ** 256 - 1;
type Float_Long is digits 20; -- 20 *decimal* digits precision at least
type Fixed_Point_Dollars is range -10 ** 10 .. 10 ** 10 delta 0.01; -- Fixed
point aka "Currency" type

There is a "modulus" type like this:

type Byte is mod 256; -- 255 + 1 = 0; 10 - 12 = 253, and so on type Wow is mod 7; -- useful for indexes: 6 + 1 = 0; 0 - 2 = 3.

2. Generics. Ada generics are the best! ;) But, they must be instanciated explicitly. Like this:

generic
    type Index is (<>); -- Index is any *discrete* type
    type Elem is private; -- Elem is any fixed-size type supporting "=" and
assignment
    type Array is array (Index) of Elem; -- Array type
    -- Also, we need a function for comparison. If it is not specified and
Elem type
    -- has overloaded "<" operation, it would be used by default.
    with function "<" (A, B : in Elem) return Boolean is <>;
procedure Generic_Sort (A : in out Array); -- body is somewhere else ;)

...

type Int_Array is array (Natural range 0 .. 20) of Integer;
procedure Sort is new Generic_Sort (Int_Array'Domain, Integer, Int_Array);

My_Array : Int_Array := (0 .. 5 => 1, 10 .. 15 => 2, 19 | 20 => 3, others =>
0);
-- look at array constant! Resulting array is (1, 1, 1, 1, 1, 1, 0, 0, 0, 0,
2, 2, 2, 2, 2, 2, 0 ... 0, 3, 3).
Sort (My_Array);

Of course, Ada is too conservative (though it really CAN be used in real development; I personally would like to use it very much, but there's no GUI library, and I don't have time to develop it - but maybe some day I will), so for D a lot of restrictions must be revised. Still, how do you like the whole idea?

3. Packages. They are like this:

-- in Foo.ads
package Foo is
    -- public part
private
    -- private part
end Foo;

-- in Foo.adb
package body Foo is
    -- body
end Foo;

While it looks so simple, Ada packages allow you to hide some details that C++ and Pascal does not allow to hide. Example: a linked list. In C++ it looks like:

struct LinkedListItem { ... }; /* this is what SHOULD be hidden, but is not! */

class LinkedList {
private:
    LinkedListItem *m_pFirst;
};

In Ada, it looks like:

generic
    type Element_Type is private;
package Linked_Lists is
    type Linked_List is private; -- it's siply private!
    Empty_List : constant Linked_List; -- private constant

    -- here are *primitive operations* -- that is, operations with this type
    -- declared in the same package where the type is declared.
    procedure Add (List : in out Linked_List; Elem : in Element_Type);
    procedure Take_Out (List : in out Linked_List; Elem : out Element_Type);
    -- this can't be a function because functions can have only IN
arguments - a
    -- strange thing, but recently I've understood that it protects you from
wrong
    -- design of your programs. Ada makes you use it's way of architecture
design;
    -- follow it or use another language, because non-Ada architecture will
never
    -- compile, I know it myself.
    function Empty (List : in List) return Boolean;

private
    type Linked_List_Item; -- forward declaration
    type Linked_List_Access is access Linked_List; -- pointer type
    type Linked_List_Item is
        record
            Data : Element_Type;
            Next : Linked_List_Access;
        end record;

    type Linked_List is
        record
            First : Linked_List_Access; -- we could add initialization like
:= null;
        end;

    Empty_List : constant Linked_List := (First => null);

end Linked_Lists;

package body Linked_Lists is
    procedure Add (List : in out Linked_List; Elem : in Element_Type) is
    begin
        ...
    end Add;
    ...
end Linked_Lists;


As you can see, Ada packages, like D modules, have one-to-one correspondence with source files. But spec and body are contained in different files, and it's very useful for navigation purposes.

In D docs, in several places you state that D compiler knows "all of the class heirarchy when generating code". It means that no separate compilation was concerned during design. You must be aware that most users want to compile a part of their program, then develop another part and compile it without knowing the first part. You must clearly understand it. Of course, to assemble a final release version, one may put all the code together, the your compiler really would know all the code. Probably this should be explained in the docs more clearly.

All right, I'm quite tired as it's now about 5:30 in the morning, and I'm going to sleep a bit. ;) Please, don't misunderstand me: I'm not criticizing D, I want to to be a really good language, not just another one. If you want D to be popular - make it better that widely used languages. It is NOT better now, it is just different. It is too simple and not-powerful. Explanation of C++ behaviour of exceptions raised during object construction took a dozen articles in MSDN ("Deep C++"). Explanation of Delphi's behaviour takes a dozen paragraphs. It does not mean Delphi is simplier and better - it means when an exception will raise in our constructor, you will have much headache and thinking as Delphi was not thought over enough. (Your destructors will get partially constructed objects! And you have to deal with it, instead of elegant solution of C++.)

Good luck!

--
Andrey Tarantsov
andreyvit@nvkz.kuzbass.net

P.S. From Russia with love. ;-)


July 11, 2002
Hello, that's me again.

Here's a small citation form Ada Rationale (part 2):

--- cut here ---

1.1  Overall Approach

Ada 95 is based on a building block approach.  Rather than providing a
number of new language features to directly solve each identified
application problem, the extra capability of Ada 95 is provided by a few
primitive language building blocks.  In combination, these building
blocks enable programmers to solve more application problems efficiently
and productively.
   Thus in the case of the object oriented area, much of the capability
is provided by the interweaving of the properties of type extension, the
child libraries and generic packages.  Great care has been taken to
ensure that the additional building blocks work together in a cohesive
and helpful manner.  Nevertheless implementation and understandability
considerations have sometimes caused some restrictions to be imposed.  An
example is that type extension of a formal generic parameter is not
permitted in a generic body (which would either break the contract model
or pose an intolerable pervasive implementation burden).

--- cut here ---

I think that is what I've tried to tell you last time.

By-the-by, look at Ada's tasking and synchronization approach. It uses two concepts: (1) a built-in multitasking support - an active object named 'task'; (2) a type with synchronized access - 'protected type'. (I can post some information here, if you like, but I think you'd better download Rationale and read it yourself - in any case it's a very interesting document, that not simply describes what is included in Ada, but also explains why it is (and what for). IMO, should be read by all people that want to be language designers.)

When calculating expressions and resolving overloads, Ada always considers the expected type. So, e.g., functions can be overloaded solely on the return value:

function Create return Linked_List;
function Create return My_Type;
...
Foo : My_Type := Create;

I like it, do you?

About generics in Ada. I forgot to say that Ada do not have generic types or classes (it does not have classes entirely). Instead, it has generic packages that may contain types or whatever. I think it's much better than generic types, because sometimes in C++ you write something like:

template <typename T> class Foo {
    // this is the nastiest: global operators must be template too
    friend Foo operator* (int Left, const Foo &Right);
public:
    // some stuff that depends on the type T
    struct Bar {T t};
    ...
};

Ada does not have classes. You simply define procedures and functions that
take your type as one of the arguments. OOP is implemented based on Ada'83's
type derivation. Record types marked with 'tagged' (i.e., they have a
'tag' - run-time information that is used to identify the type; usually it's
just a vTable pointer, but Ada standard do not specify what it is) can be
extended.

type Base is tagged
    record
        A : Integer;
    end;

-- primitive operations (those defined in the same package)
procedure Foo (Self : in out Base);
function Bar (Self : in Base) return Integer;
function Create return Base;

-- 'with record ... end record' is called a type extension;
-- Derived is a new tagged
type Derived is new Base with
    record
        B : Float;
    end record;

-- when you declare a derived type (not necessarily tagged), it inherites
all
-- primitive operations from it's base type. Some of them can be overriden:
procedure Foo (Self : in out Derived);
-- note that function Create is inherited too. But it can't return a fully
initialized
-- Derived object, because it knows only about Base! So, it is inherited as
an
-- *abstract* function, and must be overriden in Derived (or Derived will be
-- an abstract type):
function Create return Derived;

For now, Base and Derived are simply records. (They are compatible with each other.) But you can declare a variable of a 'class-wide' that can hold any type derived from the given one:

Var1 : Base;
Var2 : Base'Class := Derived'(Create); -- we explicitly call Derived's
Create
-- if you wonder, Type'(Expr) is not a type cast - it simply indicates that
Expr
-- should be of type Type. It is mainly used to specify array types in array
literals
-- and so on.

Note that Var1 can hold only Base instances, and Var2 can hold both Base and Derived (and anything else derived from Base). Ada *do not* use reference symantics, so Base'Class is an "unconstrained" type - it has variable size. Once a variable of this type is initialized, variable becomes fixed. In our example, Var2 requires explicit initialization, and after it can hold only Derived type instances. Usually pointers ('access types') are used with classes:

type Base_Only_Access is access Base; -- can point ONLY to Base instances
type Base_Access is access Base'Class; -- can point to everybody derived
from Base
Var3 : Base_Only_Access;
Var4 : Base_Access;

C++ syntax "Base Bar1" is like "Var1 : Base", and C++ "Base *Var4" is like "Var4 : Base_Access". Var2 and Var3 have no analogs in C++.

Using a class-wide type, calls to primitive operations become 'dispatched calls' (like C++/Pascal v-table calls):

Foo (Var1);        -- statically bound to Base'(Var1)
Foo (Var2);        -- dispatching call
Foo (Var3.all);    -- statically bound to Base'(Var1)
-- Pointer.all denotes the value pointed to by the pointer, like *Pointer in
C++
Foo (Var4.all);    -- dispatching call

Access types in Ada are very safe pointers. A lot of checks are made that you can't return a pointer to a local varaible or do something else that is dangerous. Some checks are done at run-time, and as far as I know they are unique to Ada, no other language do them. And they're rather useful. Before release, you remove all checks by inserting a pragma into your configuration file:

pragma Suppress (All_Checks);

Or, you can suppress only several checks, or only checks applied to the given variable / type.

Unconstrained types are very powerful in Ada. For example, array types of varying size can be declared:

type Foo is array (Integer range <>) of Integer;
-- <> is called 'box'

When you declare a variable, you must provide a constraint either explicitly or by initialization:

A : Foo (1 .. 10); -- explicit constraining
B : Foo := A; -- initialization
C : Foo := (-10 .. 10 => 0); -- initialization using array literal

You can declare a constrained subtype:

subtype Foo10 is Foo (1 .. 10);
D : Foo10; -- does not require additional care, as Foo10 is already
constrained.

Of course, unconstrained types are not dynamic, and array variables are of fixed size in Ada. But the syntax is quite suitable for dynamic arrays, isn't it? Just allow declaring uncounstrained variables and make them use reference symantics.

Another example of unconstrained type is a variant record.

type Device is (Printer, Disk);
type Request (Dev : Device) is
    record
        Handle : Interfaces.C.DWORD;
        case Dev is
            when Printer =>
                LineNo : Integer := 0;
                OutOfParer : Boolean := False;
            when Disk =>
                Head, Cyl, Track : Integer := 0;
    end record;

-- Request is unconstrained (it has a variable length!), so:
A : Request (Printer); -- constrain explicitly
B : Request := Get_Next_Req; -- by initialization
C : Request := (Dev => Disk; Head | Cyl | Track => 0); -- either
subtype Printer is Device (Printer);
D : Printer;

-- Analog of Pascal "variant record" would be:
type Request_C (Dev : Device := Printer) is
    record
        ...
    end record;

An addition of a default value to all discriminants (by-the-by, Dev is called 'a discriminant' - that is, a parameter of a type; class-wide type have a hidden discrimintant - the Tag of the contained type) turns an unconstrained type into a constrained type. So now a variable can hold any Request variant:

E : Request_C;

A := (Dev => Disk; Head | Cyl | Track => 0);
-- this is illegal, because A is constrained to Printer
E := (Dev => Disk; Head | Cyl | Track => 0);
-- this is legal, because Request_C is not an unconstrained type, so it's
dicriminants may
-- change their values

Note that you can't assign to E.Dev. To change a discrimintant, you must re-assign the whole variable's value.

That's the Ada's way of doing records. ;)

While Ada may seem a very limited language (that is, limits free fantasies of a programmer), it really cathes almost all the bugs at compile time. (I've launched debugger only a few times, to catch a really obvious errors like accessing a freed memory. And - do you know how Ada's 'free' is called? Unchecked_Deallocation. You always remember it's unsafe when you use it. ;) And when I required pointers-to-members like those in C++, I've implemented them in an hour's work! I can bet one can't implement his own sort of pointers in D. Ada's building blocks are very safe and powerful, while D currently is simply a language with C++ look and Pascal feel, with a strange mix of features.

D is still under construction. Don't you think some ideas can be borrowed from Ada? In particular, Ada's multitasking and generic packages are very nice. Ada's style of function overloading is quite nice too. And, operator overloading is implemented like this:

type My_Integer is new Integer;
function "+" (A, B : My_Integer) return My_Integer is ...;

There's no function ":=", Ada rationale clearly explains why they decided to implement assignment their own way. You define a 'controlled type':

type Foo is new Ada.Finalization.Controlled with
    record
        ...
    end record;

And the override up to three procedures:

-- initialize a newly created object of type Foo
procedure Initialize (Self : in out Foo);
-- adjust after assignment
procedure Adjust (Self : in out Foo);
-- clean-up Foo instance
procedure Finalize (Self : in out Foo);

A, B : Foo;
...
A := B;

This copies B to A bitwise, and then calls Adjust to adjust the new instance. It may seem strange and too simple, but in fact it's a very convenient way, and is enough for all applications.

Ada cycles:

while Smt loop
    ...
end loop;

for I in 1 .. 10 loop
    -- NOTE: unlike in many other languages, I is declared by the
    -- for cycle header! I's type is determined from range type. Assignments
    -- to I are illegal.
    ...
end loop;
-- I is no longer accessible here.
-- Personally I hate declaring my loop counters explicitly and love Ada's
way.

loop -- infinite loop, much nicer then "While True" or smt else
    ...
end loop;

'Break' look like this:
'exit' [loop_name] ['when' condition];

Loops can have names:

Calculate_Totals : for I in My_Array'Range loop
    while Smt_Else loop
        ...
        exit Calculate_Totals when It_Is_Friday_The_13th;
        ...
    end loop;
end loop;

Ordinary labels look unusual:

<<Label>> statement;

(But, unlike labels in other languages, Ada labels are very easy to
distinguish from code (that is, to find).)

Returning to D, I can say: don't be afraid to add unusuals into the language! No good language was similar to it's ancestors.

P.S. There are some people that regularily post to this newsgroup. Who are you? As far as I can understand, Walter is the "chief designer", am I right?

--
Andrey Tarantsov
andreyvit@nvkz.kuzbass.net


July 11, 2002
"ôÁÒÁÎÃÏ× áÎÄÒÅÊ" <andreyvit@mail.ru> wrote in message news:agi9bb$240d$1@digitaldaemon.com...
> Hello everybody!
>
> I've recently read D language spec. I can't say I like D, but I like the fact that you're crazy enough to invent your own languages and technologies - just like me. (No, I have no languages of my own.)
>
> When I was a bit younger, I've tried to invent some languages too. Now I think that the language itself does not mean that much, am inventing new programming conception, use Delphi for my everyday programming and just
love
> Ada. ;-) I want to share with you some thoughts about D.
>
> D needs much much much more designing. Currently it is like Object Pascal: you've just put together everything you like in all other languages. I
think
> it is really useful for everybody to learn Ada (by-the-by, a Pascal descendant), for that language has many samples of untraditional design.
>
> There had been a language designed for everything at once: ease of programming, reading, typing, implementation, bug making. That's ALGOL. Do you want D to be a simple language (like Pascal) or a good language? I
think
> D needs a small-to-medium redesign. I propose a discussion about the concepts of D.
>
> First. You can't put everything into a language. Probably a language
should
> contain a basic, general set of... em, capabilities (not sure it's a right word), and everything else should be defined using the language itself.
Can
> you use a "naked" C++ for real development? No, you can't. You need some sort of programming environment. C standard library is the minimum environment. STL, MFC, C++ Builder's VCL add some useful features, but
still
> I think that there's no usable programming environment for C++. But the
best
> thing in C++ is that it allows you to create a very good one. Nobody did
it,
> however. :-) But is integrating a fixed programming environment into the language a best thing?

Not, that I believe D needs much of a redesign. I do believe that it should be define in such a way that allows the language great flexibility in evolving by itself. However things that are of frequent use should be part of the standard.

> That depends on the goal of the language:
> -> for small scripting languages for quick coding it is;
> -> for real system languages I think it's not.
>
> Specifically, I'm talking about dynamic arrays and garbage collection.
While
> GC is probably OK to be integrated into the language (as for GC to be implemented using D, D must be low-level enough), but things like dynamic arrays should be implemented using standard classes. Why? Because if
dynamic
> arrays can be implemented in D in a convenient and familiar way, then many other idioms (iterators, cursors, lists) can be implemented too.

C++ was designed that way, and did they come up with anything very neat? This is just my opinion, but STL vectors were ugly. Dynamic arrays are of frequent use. Infact in most programs memory management is 80%. I would however like the ability to write my own attributes for arrays.

> Complex type. If you want to make every mathematical type a part of the language, I can tell you a lot of types that you've missed. :-) Complex
must
> be a standard class! With source code written in plain D.

Complex does seem a step away from the ordinary. I can't see how frequently I'll use it. But that's just me. On the other hand, having a complex type helps drags the datatypes of D away from C/C++. Which is a good thing.

> So that when I
> need Vector or Tensor type, I will be able to implement it as easily as
> Complex is. (Or, wouldn't you please add Tensors to D? ;)

That's what classes are for. I agree, I'd be nice to have even further control to make classes more like datatypes. I think that a language should allow you the flexibilty to add what is missing without having to use workarounds, but it should also be effecient.

> Why is D a descendant of C++, while it is much more like Pascal? The "spirit" of C++ is not a part of D, so I don't think it should look like C++. And, C++ is very self-contained language. I mean that adding
something
> new to it is not quite easy and seamless.

I'd have to strongly dissagree. It's much more like C++ the pascal syntactically and spiritily.  Although Walters previous pascal compiler experiance my shine though the cracks.

> Well, at last, syntax does not matter. Here I want to describe some
concepts
> of my favourite language (Ada) that I think could be useful for D
> developers. Ada has two versions: Ada'83 and Ada'95 (the latter having OOP
> and a few other enhancements).

Ada, it's a bit to strongly typed for me. Code in ada always seemed to me be blotted with all this type checking stuff. However it did have some good points.

> 1. Types. In Ada, there exist types and *subtypes*. Types can derive from each other. Samples:
>
> type Foo_Integer is range 0 .. 2 ** 32 - 1;
> -- Foo_Integer is a completely new type. It is not compatible with
anything
> else.


I liked that about ada (any sized data types), but then again in ada ranges lost much functionaly which became annoying.

> type Bar_Integer is new Integer range -128 .. 127;
> -- This is a *derived* type. It inherites all "primitive operations" of
type
I like this, but i don't like all the type casting problems. This is likly
to cause the need for much more casting which D tries to advoid.

> Integer, is compatible with
> -- Integer if you use explicit conversion.
> -- To call it a "signed byte" we want to add an "attribute declaration
> clause":
> for Bar_Integer'Size use 8; -- use 8 bits for this type
>
> subtype Boz_Integer is Integer range 0 .. 255;
> -- This is a subtype. It is like a synonim for other type, can be
implicitly
> converted back and forth.
>
> Int : Integer := 7;
> Foo : Foo_Integer;
> Bar : Bar_Integer;
> Boz : Boz_Integer;
>
> Foo := Int; -- this is invalid. Integer and Foo_Integer are not compatible Foo := Foo_Integer (Int); -- neither is this. They are really
*incompatible*
> ;)
> Bar := Int; -- Invalid! Thay are compatible, but they are different types.
> Bar := Bar_Integer (Int); -- Okay
> Boz := Int; -- Okay, as long as 0 <= Int <= 255. Else, Constraint_Error
> exception is raised.
> Int := Boz; -- Okay always.
>
> Ada's types are the most wonderful and logic things I've ever seen. They provide a lot of useful features not found in any other language. I think you should consider this approach.

All this strong typing blots code, which was one of the major turn downs of ada.

> Somebody has asked for very long types here. They are made very easily:
>
> type Int_256 is range 0 .. 2 ** 256 - 1;
> type Float_Long is digits 20; -- 20 *decimal* digits precision at least
> type Fixed_Point_Dollars is range -10 ** 10 .. 10 ** 10 delta 0.01; --
Fixed
> point aka "Currency" type

Yes, but if I remember correctly there was a 128bit limit in Ada 95 (which is probably more then enough).

> 2. Generics. Ada generics are the best! ;) But, they must be instanciated explicitly. Like this:
>
> generic
>     type Index is (<>); -- Index is any *discrete* type
>     type Elem is private; -- Elem is any fixed-size type supporting "="
and
> assignment
>     type Array is array (Index) of Elem; -- Array type
>     -- Also, we need a function for comparison. If it is not specified and
> Elem type
>     -- has overloaded "<" operation, it would be used by default.
>     with function "<" (A, B : in Elem) return Boolean is <>;
> procedure Generic_Sort (A : in out Array); -- body is somewhere else ;)
>
> ...
>
> type Int_Array is array (Natural range 0 .. 20) of Integer;
> procedure Sort is new Generic_Sort (Int_Array'Domain, Integer, Int_Array);
>
> My_Array : Int_Array := (0 .. 5 => 1, 10 .. 15 => 2, 19 | 20 => 3, others
=>
> 0);
> -- look at array constant! Resulting array is (1, 1, 1, 1, 1, 1, 0, 0, 0,
0,
> 2, 2, 2, 2, 2, 2, 0 ... 0, 3, 3).
> Sort (My_Array);

I liked the ability in ada's generics to specify overload operators or simply use the default. It was extremly useful in searches/sorting.  Also yo had the ability to overload any datatype operators which was useful for debuging purposes (ie counting comparsons).

On the otherhand, ADA generics are very blotted.

>
> Of course, Ada is too conservative (though it really CAN be used in real development; I personally would like to use it very much, but there's no
GUI
> library, and I don't have time to develop it - but maybe some day I will), so for D a lot of restrictions must be revised. Still, how do you like the whole idea?

First of all you point out that D is tring to be everything to everyone and simply a mash of ideas. Then you give a few more ideas.  Some of the ideas I like and some I don't. That's just my opinion. As you said "Ada is too conservative".

PS - This newsgroup is getting a "thoughts on D" type of email about once fortnight now. I'm not complaining, it's just a comment.


July 11, 2002
Hello.

First, I beg your pardon for Outlook inserting my localized name into the "From" field. I hope that is corrected now.

> Not, that I believe D needs much of a redesign. I do believe that it
should
> be define in such a way that allows the language great flexibility in evolving by itself.

Yes, definitely it should. ;)

> However things that are of frequent use should be part of the standard.

Part of the standard - yes, obviously. But should they be a part of the language, or a part of the standard library? That matters much: Pascal, for example, had a lot of procedures that required "compiler magic" - writeln, copy, etc. You could not implement your own writeln if you didn't like the standard one. I don't think it's a right way. Standard environment should be implemented using the language itself.

Talking about efficiency, nobody prevents you from doing compiler magic when compiling standard calls to optimize the usage of std. library. Still it's much better to get the same degree of efficiency by using inlining accross modules, advanced template techniques, optimizations during compilation.

> C++ was designed that way, and did they come up with anything very neat? This is just my opinion, but STL vectors were ugly.

Yes, as I've said, C++ has no good standard environment. But that does not mean the whole idea is wrong. Simply too few people understand it.

> Dynamic arrays are of frequent use. Infact in most programs memory
management is 80%. I would
> however like the ability to write my own attributes for arrays.

What are attributes?..

Yes, GC and standard useful structures are good things. Did you read C# specification? Thay have a GC too. I think C# is quite an interesting thing. By-the-by, it has dynamic arrays. ;) Don't be late with D! In it's current state D is not better than C# at least, and IMO it's worse than C++.

> On the other hand, having a complex type
> helps drags the datatypes of D away from C/C++. Which is a good thing.

Why is complex a datatype rather than a standard class???

Don't talk about efficiancy. Even GNAT has a special pragma to treat the given record like a complex type and pass it in the FPU stack. It's a special case, because Complexes really should be treated specially. But the pragma affects only the way the record is stored, and the Complex type is contained in the standard library; if you don't like it, you are free implement your own Complex (together with your own versions of trigonometric functions ;).

> That's what classes are for. I agree, I'd be nice to have even further control to make classes more like datatypes. I think that a language
should
> allow you the flexibilty to add what is missing without having to use workarounds, but it should also be effecient.

Yes, D must support templates and operator overloading. When used carefully, they do not bring in any extra overhead.

> I'd have to strongly dissagree. It's much more like C++ the pascal syntactically and spiritily.

C++ is a kind of a "metalanguage" - a language to define your own languages (environments). C++ is a middle-level language, it can be used to implement nice data types like arrays, collections, iterators, references, and then use them in real programming. That's what STL is trying to do (but not too successfully ;). With C++ macros you can change the whole look of the language.

And D is quite different - it has a predefined look & feel, with minor possibilities to extend the environment (NOT to write your own, but to extend the existing one). If you add generics and operator overloading, it would have good possibilities to extend the environment - but will never be like C++.

> Although Walters previous pascal compiler experiance my shine though the
cracks.

What did you mean?

> Ada, it's a bit to strongly typed for me. Code in ada always seemed to me
be
> blotted with all this type checking stuff.

Well... If your program is designed right, there won't be much typecasting. If during development your code starts to contain a lot of typecasts, Elaboration_Check and Accesibility_Chech workarounds, it always means you have a poor design, and the whole code is to be thrown away and rewritten in another manner. I treat it as a feature of Ada: while C++ allows any nastiest architecture to be implemented, Ada prevents you from bad choices. The first 3 Ada projects I developed had to be completely rewritten, because the original version never compiled. (Or, it did compile, with a warning that Program_Error exception will be raised at run-time, meaning that binder could not find a suitable elaboration order.)

> However it did have some good points.

Yes, it prevented most of the bugs in your programs.

> I liked that about ada (any sized data types), but then again in ada
ranges
> lost much functionaly which became annoying.

?

In fact, Ada do not allow any sized data types, there's a certain limit. But we're talking about D - and you can support anything, even 1Kbyte integers.

> I like this, but i don't like all the type casting problems. This is likly to cause the need for much more casting which D tries to advoid.

Again: there's no need for much casting if everything is designed right. And the casting that is required is required to avoid bugs. I prefer to spend more time writing a program than debugging it.

Ada's features can be compared to 8086 registers. As my old assembler book says, of course, you can store counters in ES and telephones in BP, but then you'll have problems accessing stack and managing strings. When you get used to Ada style, you start using it's features in a right way.

> All this strong typing blots code, which was one of the major turn downs
of
> ada.

Strong typing helps you write corrent code. Still, there's no need for such a strong typing in D. But you can borrow type derivation idea, and other useful Ada idioms.

> Yes, but if I remember correctly there was a 128bit limit in Ada 95 (which
>is probably more then enough).

I don't think there should be any limits (in D). Just say that any type size langer than 32 bits must be a multiplier of 32, and then implement long arithmetics. If some man requires it, why not add it?

> I liked the ability in ada's generics to specify overload operators or simply use the default. It was extremly useful in searches/sorting.  Also
yo
> had the ability to overload any datatype operators which was useful for debuging purposes (ie counting comparsons).
>
> On the otherhand, ADA generics are very blotted.

Well... Compared to C++ templates, Ada generics are truly good.

Unlike in C++, Ada generics are compiled at the time of declaration. If the generic package has successfully compiled, you know that any instanciation will be successful, because you specify the requirements for the generic paraments. C++ templates are more like extended macros.

And the idea of generic packages instead of generic types is practically useful. Why not incorporate it? Taking into consideration that D has very poor modules, packages are a suitable replacement.

By-the-by, Ada packages can be nested. That allows you to extend existent packages without modifying their code (child packages "see" the private section of their parent package). "Separate compilation" and "minimal recompilation" topics are to be studied more carefully during D design.

> First of all you point out that D is tring to be everything to everyone
and
> simply a mash of ideas.

I point out that D does not have a powerful, logical base. The basic of any language is: types, data abstraction possibilities (classes, hiding of implementation, packages), code reuse possibilities (inheritence, child packages, "programming by extension", as it's called in Ada), compatibility (interfacing to other languages and using preexistent libraries/code), portability. Complex types and dynamic arrays just don't matter. Everybody can say that in an ideal language, he wants a standard implementation of data structures and memory management (GC). That's obvious. And when you'll finish developering the basics of your language, it'll be clear how complexes and dynamic arrays should look like.

> PS - This newsgroup is getting a "thoughts on D" type of email about once fortnight now. I'm not complaining, it's just a comment.

Well, many people understand that D is steel far for ideal language...


--
Andrey Tarantsov
andreyvit@nvkz.kuzbass.net





July 11, 2002
"Andrey Tarantsov" <andreyvit@nvkz.kuzbass.net> wrote in message news:agjaae$14i4$1@digitaldaemon.com...
> Hello.
>

Attributes are like the ' in ADA

>
> > I'd have to strongly dissagree. It's much more like C++ the pascal syntactically and spiritily.
>
> C++ is a kind of a "metalanguage" - a language to define your own
languages
> (environments). C++ is a middle-level language, it can be used to
implement
> nice data types like arrays, collections, iterators, references, and then use them in real programming. That's what STL is trying to do (but not too successfully ;). With C++ macros you can change the whole look of the language.
>
> And D is quite different - it has a predefined look & feel, with minor possibilities to extend the environment (NOT to write your own, but to extend the existing one). If you add generics and operator overloading, it would have good possibilities to extend the environment - but will never
be
> like C++.

Are you kidding?
Walter has plans to implement templates in D 2.0. Have you actually used D,
because it looks like C++ to me.  You can even port (in a very round about
way) C++ classes to D and use very simular syntax methods to use them.

--I wonder what Walter opinion on D looking like pascal more then C++ is?

> > Although Walters previous pascal compiler experiance my shine though the
> cracks.

Although Walters previous pascal compiler experiance may shine though the cracks.

> What did you mean?

I simply mean (Walter correct me if I'm wrong) is that Walters written a pascal compiler before and elements of that may show in D.

>
> > Ada, it's a bit to strongly typed for me. Code in ada always seemed to
me
> be
> > blotted with all this type checking stuff.
>
> Well... If your program is designed right, there won't be much
typecasting.
> If during development your code starts to contain a lot of typecasts, Elaboration_Check and Accesibility_Chech workarounds, it always means you have a poor design, and the whole code is to be thrown away and rewritten
in
> another manner. I treat it as a feature of Ada: while C++ allows any nastiest architecture to be implemented, Ada prevents you from bad
choices.
> The first 3 Ada projects I developed had to be completely rewritten,
because
> the original version never compiled. (Or, it did compile, with a warning that Program_Error exception will be raised at run-time, meaning that
binder
> could not find a suitable elaboration order.)
>
> > However it did have some good points.
>
> Yes, it prevented most of the bugs in your programs.

Yes, but it also prevented effecient coding. Why does John Carmack use C/C++? Why are most OS written in C/C++?  Ada's a good learning language because the compiler holds your hand, but C/C++ is a power language.

> > I liked that about ada (any sized data types), but then again in ada
> ranges
> > lost much functionaly which became annoying.
>
> ?
>
> In fact, Ada do not allow any sized data types, there's a certain limit.
But
> we're talking about D - and you can support anything, even 1Kbyte
integers.

Sorry that's not what I ment there. I simply ment that you'd have to program your own operators for new types that weren't derived from variables with those operators. I was annoying when you were, say using someone elses currency type and they forgot to include a muliplication operator.

> > I like this, but i don't like all the type casting problems. This is
likly
> > to cause the need for much more casting which D tries to advoid.
>
> Again: there's no need for much casting if everything is designed right.
And
> the casting that is required is required to avoid bugs. I prefer to spend more time writing a program than debugging it.

We that's the theory anyway. In practice things turn out differn't. ADA is dying, although there has been an increase in use as a introductory language. Of coarse I don't know of any rockets that have crashed because of C mistakes. Then again ADA more of a military/machinical languange anyway. But that's beside the point.

I prefer to spend more time designing a program before writing it. I also think it depends on what your using it for. Ada is a structured programming language with OO abilities added later. C++ on the other hand is object based. Industry is swing away from structured (although it's still useful) and towards OO.

A good point about ada is that it is able to determine many errors before the program is even compiled. D is heading in that direction somewhat. Although it's keeping things more flexable.

> Ada's features can be compared to 8086 registers. As my old assembler book says, of course, you can store counters in ES and telephones in BP, but
then
> you'll have problems accessing stack and managing strings. When you get
used
> to Ada style, you start using it's features in a right way.

> > All this strong typing blots code, which was one of the major turn downs of ada.
>
> Strong typing helps you write corrent code. Still, there's no need for
such
> a strong typing in D. But you can borrow type derivation idea, and other useful Ada idioms.

> > Yes, but if I remember correctly there was a 128bit limit in Ada 95
(which
> >is probably more then enough).
>
> I don't think there should be any limits (in D). Just say that any type
size
> langer than 32 bits must be a multiplier of 32, and then implement long arithmetics. If some man requires it, why not add it?

D should support almost un-limited variable sizes. But I still want to know the limit. For example on todays proccessors it would be infeasible to have a variable 10GB integer. These things should be able to be quared at compile time like ADA allows (parhaps not using the same syntax though).

> > First of all you point out that D is tring to be everything to everyone
> and
> > simply a mash of ideas.
>
> I point out that D does not have a powerful, logical base. The basic of
any
> language is: types, data abstraction possibilities (classes, hiding of implementation, packages), code reuse possibilities (inheritence, child packages, "programming by extension", as it's called in Ada),
compatibility
> (interfacing to other languages and using preexistent libraries/code), portability. Complex types and dynamic arrays just don't matter. Everybody

As I was saying dynamic arrays are extremely important and useful. I don't
want to use a slow standard library to implement dynamic arrays. What type
of programs do you write?
(I get the idea that your into writting applications such as bussiness apps,
that arn't performance depended.)

> can say that in an ideal language, he wants a standard implementation of data structures and memory management (GC). That's obvious. And when
you'll
> finish developering the basics of your language, it'll be clear how complexes and dynamic arrays should look like.
>
> > PS - This newsgroup is getting a "thoughts on D" type of email about
once
> > fortnight now. I'm not complaining, it's just a comment.
>
> Well, many people understand that D is steel far for ideal language...
>

Actually I haven't seen anyone make the same suggestions you have. I don't believe it's in a complete form either. After all that's why it's only alpha and what this newsgroup is for.

I believe that the D should aim for a middle ground. Ada is a good learning language because it forces the programmer to do program in a particular way. The downside of this is flexibility. I think of ADA on one side of a fence and C++ on another. D remains on C++'s side of the fence and tries to be an improvement to C++.


July 11, 2002
???????? ?????? wrote:

Some good points - however I disagree with a number of them.

> Hello everybody!
> 
> I've recently read D language spec. I can't say I like D, but I like the fact that you're crazy enough to invent your own languages and technologies - just like me. (No, I have no languages of my own.)

hmm .. I have 4.

> When I was a bit younger, I've tried to invent some languages too. Now I think that the language itself does not mean that much, am inventing new programming conception, use Delphi for my everyday programming and just love Ada. ;-) I want to share with you some thoughts about D.

Ada has may ideas which make a good language - however it also has problems
primarily it is for too verbose.  (I tend to use VHDL more than Ada myself
which also has the problem that there are too many ways to do the same
operation - in my opinion there should be a minimum of ways to achieve the
same result otherwise you simply have to remember too much (or constantly
use a reference) to read another persons code.

> D needs much much much more designing. Currently it is like Object Pascal: you've just put together everything you like in all other languages. I think it is really useful for everybody to learn Ada (by-the-by, a Pascal descendant), for that language has many samples of untraditional design.

I think Ada has been examined and features added - I personally would have
liked to used an Ada style switch (case) statement,  though that idea was
rejected.

> There had been a language designed for everything at once: ease of programming, reading, typing, implementation, bug making. That's ALGOL. Do you want D to be a simple language (like Pascal) or a good language? I think D needs a small-to-medium redesign. I propose a discussion about the concepts of D.

D is designed to be a simple language - easy to write a compiler for and
easy to learn.

> First. You can't put everything into a language. Probably a language should contain a basic, general set of... em, capabilities (not sure it's a right word),

[I would have used 'features' however 'capabilities' still gets your intent]

> and everything else should be defined using the language
> itself. Can you use a "naked" C++ for real development? No, you can't. You
> need some sort of programming environment. C standard library is the
> minimum environment. STL, MFC, C++ Builder's VCL add some useful features,
> but still I think that there's no usable programming environment for C++.
> But the best thing in C++ is that it allows you to create a very good one.
> Nobody did it, however. :-) But is integrating a fixed programming
> environment into the language a best thing? That depends on the goal of
> the language:
> 
> -> for small scripting languages for quick coding it is;
> -> for real system languages I think it's not.

That seems to be an argument in favour of a meta language - however the
strength of a meta language is also its weekness,  where you are able to
redefine the language and make it look like something else you also make it
more difficult to understand (and to parse).

> Specifically, I'm talking about dynamic arrays and garbage collection. While GC is probably OK to be integrated into the language (as for GC to be implemented using D, D must be low-level enough), but things like dynamic arrays should be implemented using standard classes. Why? Because if dynamic arrays can be implemented in D in a convenient and familiar way, then many other idioms (iterators, cursors, lists) can be implemented too.

Garbage collection,  although necessary for the language,  is implemented in a library not as part of the main language.

> Complex type. If you want to make every mathematical type a part of the language, I can tell you a lot of types that you've missed. :-) Complex must be a standard class! With source code written in plain D. So that when I need Vector or Tensor type, I will be able to implement it as easily as Complex is. (Or, wouldn't you please add Tensors to D? ;)
> 
> Why is D a descendant of C++, while it is much more like Pascal? The "spirit" of C++ is not a part of D, so I don't think it should look like C++. And, C++ is very self-contained language. I mean that adding something new to it is not quite easy and seamless.

D is not a descendant of C++, it is a descendant of C.  That idea being
that D is what C++ should/could have been.  The idea being to step away
from the complexity of C++ which is underused, poorly implemented and often
leads to bugs.

> Well, at last, syntax does not matter. Here I want to describe some concepts of my favourite language (Ada) that I think could be useful for D developers. Ada has two versions: Ada'83 and Ada'95 (the latter having OOP and a few other enhancements).

(some of the following features would be useful - however there syntax would need a complete overhaul to be used in D).

> 1. Types. In Ada, there exist types and *subtypes*. Types can derive from each other. Samples:

[-snip-]

Most of this can be achieved with 'define' and 'alias' - a range check would be useful though.

> 2. Generics. Ada generics are the best! ;) But, they must be instanciated explicitly. Like this:

[-snip-]

D generics (templates) have been left out till version 2 - their implementation is still under discussion.

> 3. Packages. They are like this:

[-snip-]

The trouble with this is that when a procedure is redefined the package header also has to be modified.  While this is not a major problem it is very annoying.  I believe D can achieve the same as Ada here despite the difference in syntax.

> Explanation of C++ behaviour of exceptions raised during object construction took a dozen articles in MSDN ("Deep C++").

The idea of D is to simplify problems such as this,  therefore making the language easier to implement properly.  I do not believe there is a single implementation of C++ which fully conforms to the standard,  this should not be the case in D.

> Explanation of Delphi's behaviour takes a dozen paragraphs. It does not mean Delphi is simplier and better - it means when an exception will raise in our constructor, you will have much headache and thinking as Delphi was not thought over enough. (Your destructors will get partially constructed objects! And you have to deal with it, instead of elegant solution of C++.)

I can not comment on Delphi,  however 'elegant' is not a word I would use to describe C++.

C 2002/7/11
July 11, 2002
???????? ?????? wrote:

> Hello, that's me again.

And me replying again.

[-snip-]

> By-the-by, look at Ada's tasking and synchronization approach. It uses two concepts: (1) a built-in multitasking support - an active object named 'task'; (2) a type with synchronized access - 'protected type'.

I think Ada is still the best language for inbuilt multitasking support, the synchronisation directive on D (in my opinion) is inadiquate and ill defined - however this is just an alpha versions and that should improve.

> (I can
> post some information here, if you like, but I think you'd better download
> Rationale and read it yourself - in any case it's a very interesting
> document, that not simply describes what is included in Ada, but also
> explains why it is (and what for). IMO, should be read by all people that
> want to be language designers.)

I has been a while since I read that - so my memory may be a little patchy on the subject.

> When calculating expressions and resolving overloads, Ada always considers the expected type. So, e.g., functions can be overloaded solely on the return value:
> 
> function Create return Linked_List;
> function Create return My_Type;
> ...
> Foo : My_Type := Create;
> 
> I like it, do you?

It is useful,  however I believe it may interfere with D's automatic type conversions (a feature I disagree with,  but useful when converting C programmes).

[-snip-]

> Access types in Ada are very safe pointers. A lot of checks are made that you can't return a pointer to a local varaible or do something else that is dangerous. Some checks are done at run-time, and as far as I know they are unique to Ada, no other language do them. And they're rather useful. Before release, you remove all checks by inserting a pragma into your configuration file:
>
> pragma Suppress (All_Checks);

D's debug mode serves the same purpose (currently debug mode cannot be
disabled however - this should change on later versions).

> Or, you can suppress only several checks, or only checks applied to the given variable / type.
> 
> Unconstrained types are very powerful in Ada. For example, array types of varying size can be declared:

[-snip-]

D dynamic arrays serve a similar purpose - they are not quite as flexable as the Ada implementation however I suspect this additional flexibility can be done without.

> While Ada may seem a very limited language (that is, limits free fantasies of a programmer), it really cathes almost all the bugs at compile time.
[unlike your spell checker - sorry could not resist that joke]
> (I've launched debugger only a few times, to catch a really obvious errors like accessing a freed memory. And - do you know how Ada's 'free' is called? Unchecked_Deallocation. You always remember it's unsafe when you use it. ;) And when I required pointers-to-members like those in C++, I've implemented them in an hour's work! I can bet one can't implement his own sort of pointers in D. Ada's building blocks are very safe and powerful, while D currently is simply a language with C++ look and Pascal feel, with a strange mix of features.

In my opinion it is more a C look with object oriented features,  dynamic
arrays and properties.  D is more for programmers who want to get the job
done and while Ada may be safe sometimes you just do not want that safety.

> D is still under construction. Don't you think some ideas can be borrowed from Ada? In particular, Ada's multitasking and generic packages are very nice. Ada's style of function overloading is quite nice too. And, operator overloading is implemented like this:

As these are things which are currently not fully defined in D they could be included using an Ada style implementation (though of course with D style syntax).

> Ada cycles:

Looks just like BASIC in my opinion.

> 'Break' look like this:
> 'exit' [loop_name] ['when' condition];

Could do with D using
        <label> : while( <condition> ) {
                if( <condition> ) break <label>;
        }

> Returning to D, I can say: don't be afraid to add unusuals into the language! No good language was similar to it's ancestors.

A departure from C is not a problem - only the features required for easy
migration of C programmers should be kept (with the exception of the switch
statement fall though - an endless source of bugs).  Otherwise the D
language should be internally consistant.

> P.S. There are some people that regularily post to this newsgroup. Who are you? As far as I can understand, Walter is the "chief designer", am I right?

Yes.

July 11, 2002
> Have you actually used D, because it looks like C++ to me.

No, I did not. I don't argue that D does not look like C++. The look can be easily changed in a few days by rewriting compiler's syntax analyzer. I say that the basic concepts of D are more like C++'s ones.

>  You can even port (in a very round about way) C++ classes to D
> and use very simular syntax methods to use them.

That matters nothing. You can port C++ classes to Delphi very easily. In fact, you can even write a program that does it automatically. But there are a lot of C++ applications (I don't mean "programs", just "ways to use C++") that cannot be ported to D or Pascal. In fact, D is *very* similar to C#.

They key features of C++ that make it feel like C++ are: templates, macros, overloading of operators like ->, [], new, delete. Using this, you can make anything look like anything else. That's the philosophy of C++, but not of Pascal, D, Java or C#. Among all these, I would prefer C# as the most balanced language. If I had much time (and wish) to spend on this, I would probably write a C++ environment that would suit me. But it's not an easy job.

> Yes, but it also prevented effecient coding. Why does John Carmack use C/C++? Why are most OS written in C/C++?  Ada's a good learning language because the compiler holds your hand, but C/C++ is a power language.

OK, all this is becoming a flame. I don't think we should discuss languages as they are, but instead let's talk about concrete conceptions that can be utilitized in D. And, OSes are written in C/C++ because it allowes a very low-level code. Low-level does not mean only "very efficient", simply when writing OS kernel you do not need any of your language services (in particular, you wouldn't use dynamic arrays to store non-paged memory pool). Also, C is used due to historical reasons.

Yes, C/C++ ("... OK, let's flame a bit...") is a powerful language when you want to design a new environment. If you want simply to write programs, any language whose ready-made environment suits your needs will do. Yes, I some things (like lexical parsers) are always better expressed in C++ because of it's pointer arithmetic. I think that's enough about the languages.

> I prefer to spend more time designing a program before writing it. I also think it depends on what your using it for.

By-the-by, what is D targetting for?

> A good point about ada is that it is able to determine many errors before the program is even compiled. D is heading in that direction somewhat. Although it's keeping things more flexable.

Unfortunately these aims might not be compatible. Either the language limits you (limits not _what_ you can write, but only _how_ you can write it) and detects your errors, or the language allows you to write everything you want how you want it, but then all mistakes are your responsibility.

> D should support almost un-limited variable sizes. But I still want to
know
> the limit. For example on todays proccessors it would be infeasible to
have
> a variable 10GB integer.

Show me a man that wants 10GB integers, I'll release a special compiler version for him (if he sends me an IA-64 processor and 10GB of RAM).

> As I was saying dynamic arrays are extremely important and useful. I don't want to use a slow standard library to implement dynamic arrays.

In what way shall std. library slow down dynamic arrays? Let's take C++.

template <class T>
class dyn_array {
public
    T &operator [] (int index);
...
};

When dyn_array::operator[] is called, it returns a reference to the array item. After you compile this and apply proper optimizations (inlining), I don't think there would be a way to implement dynamic arrays faster. Standard library does not slow your code! If the code written in D is inefficient, then fast dynamic arrays won't rescue your turtle app.

The thing I was talking about: there should be a way to implement in D, if I would like so, dynamic arrays, static interlocked lists or whatever. You do understand it, so I don't think this question needs additional discussion.

> What type of programs do you write?

Just common Windows programs. (And, for fun, some libraries and small apps
in languages like Ada.)

And what sort of programs do YOU write? Are they real-time reactor control systems? Or probably a system software for winged missiles? I guess that you simply love efficiency. And, for multimedia applications or other time-critical sections, even C# has sections marked with 'unsafe' where pointer arithmetic can be used. Maybe this is the right way of thinking: the most of your app needs to be stable, and some critical parts should be as fast as possible (after a few days of debugging ;).

> The downside of this is flexibility.

Have you seen ALGOL? I can tell you: you'll love it! There nothing more flexible in the whole world.

***

And now my proposal.

Languages cannot be invented and designed in the way D is. First, everybody should say how do they see the language of their dreem (or, probably, just how do they think D should look like and what should it contain). Then, all the proposals should be grouped, filtered and generalized. Then, you choose what basic conceptions your language will be built on. And then, using these conceptions, you try to produce a final language.

D was designed in this way: you took C++, throw away everything you disliked, added everything you liked, submitted specification, throw away everything that is hard to implement, and wrote the alpha version of the compiler. That won't do. All the factors (ease of implementation, ease of understanding, ease of writing programs, ease of maintaining programs, ease of writing correct code and finding bugs) must be considered from the very beginning, and all the features should make up a self-contained Language, not just a set of features under the common name.

Here's a wrong list of study topics:
WS1. Modules.
WS2. Syncronization.
WS3. Generics.

As I can understand, current study topics are as follows.

S1. Separate compilation. It is known that a program divided into modules is easier to write, debug, understand and maintain. D should provide a support for some kind of modules.

S2. Symultaneous execution capabilities (whether multitasking should be incorporated into the lang, how should tasks communicate, how will they access shared data).

S3. Improve code reuse. This includes generics, probably macros (I don't like them much, and you don't like them, so probably we can forget about them), nested modules like packages of Ada'95 (so that you can extend an existent library without altering it's source code). Ada team said they considered "other types of type extension", that is, derivation of enumerations, extending ordinary records and so on. They gave up the idea because it's hard to implement. Should we?

I think development of D should be a bit more organized. We should collect and keep all the ideas everybody has posted, we should add our ideas, then probably we should look at all the ideas and exchange our thought about revising the specification. Then we should revise it a few times until something very good is produced.

2Walter: probably it's time to give your comments about the overall discussion... What do you think about revising the lang?

Regards!

--
Andrey Tarantsov.

July 11, 2002
> The idea of D is to simplify problems such as this,  therefore making the language easier to implement properly.  I do not believe there is a single implementation of C++ which fully conforms to the standard,  this should not be the case in D.
> 

To be fair to C++, although I am admittedly not an advocate of the language, Doctor Dobbs did a "benchmark" for compliance of sorts and the major compilers are very largely compliant.  (of course its the little things that kill).  GCC did *remarkably* well with standards compliance for C++ (I expected it to fair horribly) as did Borland and some others that I don't really know anything about.  Can you guess which compiler was *least* compliant with the standards....?  hummm?  (take a wild guess) ;-)

-Andy


> 
>>Explanation of Delphi's behaviour takes a dozen paragraphs. It does not
>>mean Delphi is simplier and better - it means when an exception will raise
>>in our constructor, you will have much headache and thinking as Delphi was
>>not thought over enough. (Your destructors will get partially constructed
>>objects! And you have to deal with it, instead of elegant solution of
>>C++.)
> 
> 
> I can not comment on Delphi,  however 'elegant' is not a word I would use to describe C++.
> 
> C 2002/7/11


July 11, 2002
I use Delphi and C++, Borland and Microsoft's

I do prefer Delphi for client applications. I do however think Java and C#
are better languages than everything, however I had to dismiss using them
for client applications long ago. Delphi Pascal is not the best language,
but all in all it makes for the best development environment. I do have to
use C++ for some things, such as those which might want to statically link
ImageMagick or other large and fast moving excellent 3rd party C/C++ based
libraries... The C interop capabilities of D would be useful there as
well, but that's secondary to the fact that C is like a compiled Java.
I also do some BCB .obj linking in Delphi, but some things, such as
ImageMagick can not be compiled in BCB without a ton of work.

D seems to fill an important niche, which I wanted filled years ago...

You sound like those Delphi people who think of C# as a Delphi ripoff and are completely ignorant of Java... That makes it hard to pay attention... I am just a little tired of ignorant Delphi users. Remember, I am a Delphi user, just not an ignorant one.

D has a chance to overthrow Delphi in a lot of applications, especially mine. It will need a well designed library and a RAD IDE. It's simple...

-Toyotomi

« First   ‹ Prev
1 2 3 4 5 6