www.digitalmars.com         C & C++   DMDScript  

D - Some questions and suggestions, and the future of D

reply =?koi8-r?B?9MHSwc7Dz9cg4c7E0sXK?= <andreyvit mail.ru> writes:
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. ;-)
Jul 10 2002
next sibling parent reply =?koi8-r?B?9MHSwc7Dz9cg4c7E0sXK?= <andreyvit mail.ru> writes:
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
Jul 10 2002
next sibling parent C.R.Chafer <blackmarlin nospam.asean-mail.com> writes:
???????? ?????? 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.
Jul 11 2002
prev sibling parent "Sean L. Palmer" <seanpalmer earthlink.net> writes:
"Таранцов Андрей" <andreyvit mail.ru> wrote in message
news:agj31a$tt$1 digitaldaemon.com...
 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).
Like I said, I believe in the building block approach. The language should allow you to build very fundamental types (such as a rangechecked replacement for int) without any additional overhead than the builtin type had. Part of what you need to be able to do that is to be able to hide the fact that a class is user-defined. That means, to not generate any debug info about the methods of the class, so that the debugger will not step into those methods (this is annoying for very basic classes such as string or vector or bignumber or date). You need debug info when first making the class, or when debugging it. Later when it's completely solid and bugfree, you should be able to disable debug info for any class or module.
 --- 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?
I'm ok with that. I'd also want to be able to return tuples.
 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.
I have thought that the OOP syntax sugar may be entirely unnecessary. I guess the designers of ADA did too. I think the main problem with using ADA today is that it does not have any concept of inheritance.
 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;
I find this distinction between procedure and function to be silly. Unless you restrict functions so that they may not ever have side effects and are completely deterministic. (i.e. if I call it twice with the same inputs, I'll definitely get the same outputs both times, so the compiler is safe to cache the first result and just use it twice)
 -- '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;
Interesting.
 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.
I don't see the distinction between that and a typecast.
 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++.
interesting.
 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:
If you remove all checks, your program might only fail once you release it. ;) But performance is necessary.
 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. ;)
Still very interesting.
 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 ...;
I prefer the pattern matching approach used in O'CaML.
 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.
I only tried a little, but was unable to think of a case where it wouldn't work.
 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.
I like this style of foreach iteration. Should work on ranges, enumerations, arrays, or other containers.
 loop -- infinite loop, much nicer then "While True" or smt else
     ...
 end loop;
Yes.
 '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;
It looks like a variable declaration. Confusing.
 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).)
That's not bad. << and >> are used for shifts in D though. May be a conflict.
 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.
Yeah but you want to keep it readable and sane.
 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? I'm one. Walter is the head honcho.
 --
 Andrey Tarantsov
 andreyvit nvkz.kuzbass.net
I think what I want is a language with alot of D's design goals. But it is not D because of lack of generics and operator overloading and so you can't make your own basic types. I need my own basic types because I do alot of low level 3D math programming and I need vectors, quaternions, and matrices or I can't get anything done, and they read much better with overloaded operators than with function calls. Fixed-size D arrays are very similar to SIMD register types already and have some good operations, but they don't support saturation or fixed point. And they don't have dot product etc. Modern CPU's also have reciprocal square root instructions etc that are not currently exposed in D. Games programming would be much better if it were not done in C and C++. No other languages even come close to being usable for professional games development (yet). Maybe I should make a language. One of these days.... ;) Sean
Jul 12 2002
prev sibling next sibling parent reply "anderson" <anderson firestar.com.au> writes:
"Таранцов Андрей" <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.
Jul 10 2002
next sibling parent reply "Andrey Tarantsov" <andreyvit nvkz.kuzbass.net> writes:
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?.. By-the-by, it has dynamic arrays. ;) Don't be late with D! In it's current
 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
Jul 11 2002
parent reply "anderson" <anderson firestar.com.au> writes:
"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++.
Jul 11 2002
next sibling parent reply "Andrey Tarantsov" <andreyvit nvkz.kuzbass.net> writes:
 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++") 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 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 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.
Jul 11 2002
parent "anderson" <anderson firestar.com.au> writes:
"Andrey Tarantsov" <andreyvit nvkz.kuzbass.net> wrote in message
news:agk0j6$1lml$1 digitaldaemon.com...
 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.

 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

 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.
I don't like that idea. Program languagues need to be standard. If you redeign the basic flow or look of the language you not only end up working against the grain, but you make it difficult for other users to understand your code. Macros also make compliation ineffecient because the compilier has extra processing steps.
 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.
It was not ment a a flame. But I think this type of talk is expected when discussing language design. There's alot of personal opinions out there. D also allows for low-level code. You don't have to use dynamic arrays. The GC can be turned off.
 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?
run-time language.
 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.
There's always a toss-up between one thing and another. In rare cases you can have both.
 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).
That's the idea. I simply ment I want the MAX value.
 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.
That's un-true. The more the complier knows about a program, the better it can optimise it. If it doesn't know that your writting a dynamic array lib, then how is it going to be-able to ie make it take advantage of parellel proccessing?
 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

 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 ;).
It was just out of interest (probably shouldn't have hadded that Guestimate). No need to start a flame. 3d programming is my hobby. 3D editors and engines. They need to be fast, and speed is 90% in the design.
 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.
No I haven't. I said I aim for something in-between.
 ***

 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.
Then we'd have to call it something else. As C was an extention of B and C++ of C we can't break that cycle. D is ment to be a new programming language based on C/C++. This is both for quick learning times and because C is the most popular language of all time.
 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.
But D can be divided into modules?
 S2. Symultaneous execution capabilities (whether multitasking should be
 incorporated into the lang, how should tasks communicate, how will they
 access shared data).
D has support for this although I haven't used it.
 S3. Improve code reuse. This includes generics, probably macros (I don't
Generics are planned for 2.0.
 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).
That's what classes are for.
 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?
Yes I'd be interested too.
 Regards!

 --
 Andrey Tarantsov.
Anyway enough said, because we are beginning to repeat ourselves.
Jul 11 2002
prev sibling parent reply "Walter" <walter digitalmars.com> writes:
"anderson" <anderson firestar.com.au> wrote in message
news:agjp40$195r$1 digitaldaemon.com...
 --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.
It's true that the first compiler I wrote was for a Pascal subset, way back in 1980 or so. While Pascal is not my favorite language, it does have a nice feature I tried to carry into D - that of being able to separate the lexical, syntactic, and semantic phases of compilation. This is a crucial feature for reducing a complicated language into managable pieces, for easy understanding and implementation.
Jul 19 2002
parent reply "Sean L. Palmer" <seanpalmer earthlink.net> writes:
Sets and ranges were both quite useful.

You can't use ++ and -- on enum variables in C++... can you in D?

Sean

"Walter" <walter digitalmars.com> wrote in message
news:ahah9f$m73$1 digitaldaemon.com...
 "anderson" <anderson firestar.com.au> wrote in message
 news:agjp40$195r$1 digitaldaemon.com...
 --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.
It's true that the first compiler I wrote was for a Pascal subset, way
back
 in 1980 or so. While Pascal is not my favorite language, it does have a
nice
 feature I tried to carry into D - that of being able to separate the
 lexical, syntactic, and semantic phases of compilation. This is a crucial
 feature for reducing a complicated language into managable pieces, for
easy
 understanding and implementation.
Jul 20 2002
parent reply "Walter" <walter digitalmars.com> writes:
"Sean L. Palmer" <seanpalmer earthlink.net> wrote in message
news:ahci0h$47g$1 digitaldaemon.com...
 Sets and ranges were both quite useful.
 You can't use ++ and -- on enum variables in C++... can you in D?
You know, I never thought of that. What do you think?
Jul 20 2002
next sibling parent reply Russ Lewis <spamhole-2001-07-16 deming-os.org> writes:
Walter wrote:

 "Sean L. Palmer" <seanpalmer earthlink.net> wrote in message
 news:ahci0h$47g$1 digitaldaemon.com...
 Sets and ranges were both quite useful.
 You can't use ++ and -- on enum variables in C++... can you in D?
You know, I never thought of that. What do you think?
I would vote no, because I think that enums should be a different "idea space" than integers. I'm likely to get outvoted, though, and that's ok. -- The Villagers are Online! http://villagersonline.com .[ (the fox.(quick,brown)) jumped.over(the dog.lazy) ] .[ (a version.of(English).(precise.more)) is(possible) ] ?[ you want.to(help(develop(it))) ]
Jul 21 2002
next sibling parent reply Pavel Minayev <evilone omen.ru> writes:
On Sun, 21 Jul 2002 22:32:14 -0700 Russ Lewis 
<spamhole-2001-07-16 deming-os.org> wrote:

 You can't use ++ and -- on enum variables in C++... can you in D?
You know, I never thought of that. What do you think?
I would vote no, because I think that enums should be a different "idea space" than integers. I'm likely to get outvoted, though, and that's ok.
Me, I like that feature of Pascal. Makes sense sometimes, when you have a set of sequential elements, and want to traverse back and forth. At least it doesn't hurt in other cases. =)
Jul 21 2002
parent reply "anderson" <anderson firestar.com.au> writes:
	charset="iso-8859-1"
Content-Transfer-Encoding: quoted-printable

Enums with integer properties (++, --) would be nice. I sometimes like =
to mix integers and enums together. For example I may use the last 8 =
places for a byte storage and the first part for enable/disable bit =
flags. Although now D has bits included, it's still useful in things =
such as file saving. ++, -- and any other integer maths would be useful =
on enums, although I suppose it's possible to cast an enum to a int.=20

Also how about a specific structure or extention to enums for enable =
disable bits. I know that D's bits data type goses some way, but it =
doesn't provide a labling system enable/disable bits. And before you =
point it out, you could use:

enum EnableBit //You may reconise this from GL (Although it's missing a =
few)
{
    ALPHA_TEST =3D 1,
    AUTO_NORMAL =3D 2,
    BLEND =3D 4,
    COLOR_MATERIAL =3D 8,
    CULL_FACE =3D 16,
    DEPTH_TEST =3D 32,
    DITHER =3D 64,
    FOG =3D 128,
    LIGHTING =3D256,
    LINE_SMOOTH =3D 1024,
    LINE_STIPPLE =3D 2048,
    LOGIC_OP =3D 4096,
    NORMALIZE =3D 8192,
    POINT_SMOOTH =3D 16384,
    POLYGON_SMOOTH =3D 32768,
    POLYGON_STIPPLE =3D 65536,
    SCISSOR_TEST =3D 131072,
    STENCIL_TEST =3D 262144,
    TEXTURE_1D =3D 524288,
    TEXTURE_2D =3D 1048576
};

EnableBit CurrentEnable;

CurrentEnable &=3D ALPHA_TEST;
ect...


-------------------------------------------------------------------------=
-------


But how about

enable EnableBit
{
ALPHA_TEST, //Auto generates the numbers

...
};

EnableBit CurrentEnable;

CurrentEnable &=3D ALPHA_TEST;

And even syntax sugur,

CurrentEnable.enable(ALPHA_TEST);
CurrentEnable.disable(ALPHA_TEST);
ect...


"Pavel Minayev" <evilone omen.ru> wrote in message =
news:CFN37459427319294 news.digitalmars.com...
 On Sun, 21 Jul 2002 22:32:14 -0700 Russ Lewis=20
 <spamhole-2001-07-16 deming-os.org> wrote:
=20
 You can't use ++ and -- on enum variables in C++... can you in D?
You know, I never thought of that. What do you think?
=20 I would vote no, because I think that enums should be a different =
"idea
 space" than integers.
=20
 I'm likely to get outvoted, though, and that's ok.
=20 Me, I like that feature of Pascal. Makes sense sometimes, when you have a set of sequential elements, and want to traverse back and forth. At least it doesn't hurt in other cases. =3D) =20
Jul 22 2002
parent "anderson" <anderson firestar.com.au> writes:
	charset="iso-8859-1"
Content-Transfer-Encoding: quoted-printable


  "anderson" <anderson firestar.com.au> wrote in message =
news:ahglim$12gp$1 digitaldaemon.com...
  Enums with integer properties (++, --) would be nice. I sometimes like =
to mix integers and enums together. For example I may use the last 8 =
places for a byte storage and the first part for enable/disable bit =
flags. Although now D has bits included, it's still useful in things =
such as file saving. ++, -- and any other integer maths would be useful =
on enums, although I suppose it's possible to cast an enum to a int.=20

  Also how about a specific structure or extention to enums for enable =
disable bits. I know that D's bits data type goses some way, but it =
doesn't provide a labling system enable/disable bits. And before you =
point it out, you could use:

  enum EnableBit //You may reconise this from GL (Although it's missing =
a few)
  {
      ALPHA_TEST =3D 1,
      AUTO_NORMAL =3D 2,
      BLEND =3D 4,
      COLOR_MATERIAL =3D 8,
      CULL_FACE =3D 16,
      DEPTH_TEST =3D 32,
      DITHER =3D 64,
      FOG =3D 128,
      LIGHTING =3D256,
      LINE_SMOOTH =3D 1024,
      LINE_STIPPLE =3D 2048,
      LOGIC_OP =3D 4096,
      NORMALIZE =3D 8192,
      POINT_SMOOTH =3D 16384,
      POLYGON_SMOOTH =3D 32768,
      POLYGON_STIPPLE =3D 65536,
      SCISSOR_TEST =3D 131072,
      STENCIL_TEST =3D 262144,
      TEXTURE_1D =3D 524288,
      TEXTURE_2D =3D 1048576
  };

  EnableBit CurrentEnable;

Should be...

CurrentEnable |=3D ALPHA_TEST; //Enable bit
  ect...


-------------------------------------------------------------------------=
-----


  But how about

  enable EnableBit
  {
  ALPHA_TEST, //Auto generates the numbers

  ...
  };

  EnableBit CurrentEnable;

Should be...

CurrentEnable |=3D ALPHA_TEST; //Enable bit

  And even syntax sugur,

  CurrentEnable.enable(ALPHA_TEST);
  CurrentEnable.disable(ALPHA_TEST);
  ect...


  "Pavel Minayev" <evilone omen.ru> wrote in message =
news:CFN37459427319294 news.digitalmars.com...
  > On Sun, 21 Jul 2002 22:32:14 -0700 Russ Lewis=20
  > <spamhole-2001-07-16 deming-os.org> wrote:
  >=20
  > >> > You can't use ++ and -- on enum variables in C++... can you in =
D?
  > >>
  > >> You know, I never thought of that. What do you think?
  > >=20
  > > I would vote no, because I think that enums should be a different =
"idea
  > > space" than integers.
  > >=20
  > > I'm likely to get outvoted, though, and that's ok.
  >=20
  > Me, I like that feature of Pascal. Makes sense sometimes, when you
  > have a set of sequential elements, and want to traverse back and
  > forth. At least it doesn't hurt in other cases. =3D)
  >=20
Jul 22 2002
prev sibling parent "Sandor Hojtsy" <hojtsy index.hu> writes:
"Russ Lewis" <spamhole-2001-07-16 deming-os.org> wrote in message
news:3D3B98DE.CDF15BC deming-os.org...
 Walter wrote:

 "Sean L. Palmer" <seanpalmer earthlink.net> wrote in message
 news:ahci0h$47g$1 digitaldaemon.com...
 Sets and ranges were both quite useful.
 You can't use ++ and -- on enum variables in C++... can you in D?
You know, I never thought of that. What do you think?
I would vote no, because I think that enums should be a different "idea space" than integers.
Hmm.. Sometimes I use enum for naming the states of a process. In this idea space it seems logical to read ++ as "step into the next state". So please implement it. I admit, there are some problems with the analogy: steping to the next state, does not necessarily mean "increment the underlying integer value with 1". Especially when the last state is reached. OTOH, there are cases when I use enums as a collection of unique values with names, but the particular value is not important. In these cases I would be really happy if the compiler would check that I do no integer operations on these values. Summary: The best would be two enum types! One with all integer operations (enum alias), and one without any (enum typedef). Yours, Sandor
Jul 23 2002
prev sibling parent reply Jonathan Andrew <jon ece.arizona.edu> writes:
Walter wrote:
 
 
 
 You know, I never thought of that. What do you think?
 
It seems enums (anonymous especially) are used a lot for constants, so it doesn't seem appropriate to modify them like that. Just my opinion, Jon
Jul 21 2002
parent Jonathan Andrew <jon ece.arizona.edu> writes:
that got posted in the wrong place, Sorry!
 
Jul 21 2002
prev sibling parent "OddesE" <OddesE_XYZ hotmail.com> writes:
"anderson" <anderson firestar.com.au> wrote in message
news:agj38p$12r$1 digitaldaemon.com...
<SNIP>
 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.
Yeah but that is a good sign! It means many people are discovering D and are trying to share their opinions on it. It is logical they want to give their view on D when they first get here. Andrey, welcome and thank you for your input. -- Stijn OddesE_XYZ hotmail.com http://OddesE.cjb.net _________________________________________________ Remove _XYZ from my address when replying by mail
Jul 13 2002
prev sibling next sibling parent reply C.R.Chafer <blackmarlin nospam.asean-mail.com> writes:
???????? ?????? 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
Jul 11 2002
next sibling parent andy <acoliver apache.org> writes:
 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
Jul 11 2002
prev sibling parent reply "Andrey Tarantsov" <andreyvit nvkz.kuzbass.net> writes:
Hello!

2Toyotomi:


 are completely ignorant of Java...
because I like it & .NET Framework, and because I'm subscribed to MSDN descendant. Java... well, I don't like it, but I did not have a chance to use it, so there's no serious opinion.
 D is designed to be a simple language - easy to write a compiler for and
 easy to learn.
This does not mean it would be easy to program with it. Standard Pascal is a very simple language, but it's very hard to write anything useful.
 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).
Yes, I like the idea of metalanguages, but I'm also a bit tired of them, because there are no good class libraries, and I don't like writing everything myself. FYI, do you know that C++ STL is originally borrowed from Ada Generics Library developed in early 1980s?
 Garbage collection,  although necessary for the language,  is implemented
 in a library not as part of the main language.

 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.
That's interesting. I like the idea to make a "good & easy to use C++". All they're too high-level anyway. I can tell you that making a better C++ is a *very* serious... job. OK, going to think about the question. By-the-by, what do you think about exceptions? As for me, I consider using classes for them usual, but nonneccessary. Anyway, I'm too lazy to define my own full-featured classes, so e.g. in Delphi I always write "ESmt = class (Exception);". Don't you think exceptions should not be classes? 1. Allowing to throw only descendents of a specific class (e.g. CException) is a strange rule. 2. This would be ideal: class EBadToken : exception {public: string file; int line, col;}; throw EBadToken ("My File", my_line, my_col); Something like this: when a class has no constructors and has only public fields, it gets a constructor that can accepts arguments corresponding to all the fields and initializes them. This is not a proposal, it's just an idea to discuss. G/L!
Jul 11 2002
next sibling parent "Sean L. Palmer" <seanpalmer earthlink.net> writes:
"Andrey Tarantsov" <andreyvit nvkz.kuzbass.net> wrote in message
news:aglpvi$qc0$1 digitaldaemon.com...
 Hello!

 2Toyotomi:


and
 are completely ignorant of Java...
because I like it & .NET Framework, and because I'm subscribed to MSDN descendant. Java... well, I don't like it, but I did not have a chance to use it, so there's no serious opinion.
I programmed in Pascal for like 8 years before I got sick of it and switched to C++.
 D is designed to be a simple language - easy to write a compiler for and
 easy to learn.
This does not mean it would be easy to program with it. Standard Pascal is
a
 very simple language, but it's very hard to write anything useful.
D has enough power to be useful in real-world programming. I've done a little OpenGL and Direct3D programming with it already. ;)
 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).
Yes, I like the idea of metalanguages, but I'm also a bit tired of them, because there are no good class libraries, and I don't like writing everything myself. FYI, do you know that C++ STL is originally borrowed from Ada Generics Library developed in early 1980s?
 Garbage collection,  although necessary for the language,  is
implemented
 in a library not as part of the main language.

 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.
That's interesting. I like the idea to make a "good & easy to use C++".
All

opinion,
 they're too high-level anyway.

 I can tell you that making a better C++ is a *very* serious... job. OK,
 going to think about the question.

 By-the-by, what do you think about exceptions? As for me, I consider using
 classes for them usual, but nonneccessary. Anyway, I'm too lazy to define
my
 own full-featured classes, so e.g. in Delphi I always write "ESmt = class
 (Exception);". Don't you think exceptions should not be classes?
I never use exceptions because all the C++ implementations I've tried slow down alot when you turn them on.
 1. Allowing to throw only descendents of a specific class (e.g.
CException)
 is a strange rule.
 2. This would be ideal:

 class EBadToken : exception {public: string file; int line, col;};

 throw EBadToken ("My File", my_line, my_col);
file, line and col should be implicit, and if you're running under a debugger, are completely unnecessary.
 Something like this: when a class has no constructors and has only public
 fields, it gets a constructor that can accepts arguments corresponding to
 all the fields and initializes them.
I like that syntax sugar.
 This is not a proposal, it's just an idea to discuss.
Why not make it a proposal? I propose that we propose to discuss your idea. ;) Sean
Jul 12 2002
prev sibling parent reply "Walter" <walter digitalmars.com> writes:
"Andrey Tarantsov" <andreyvit nvkz.kuzbass.net> wrote in message
news:aglpvi$qc0$1 digitaldaemon.com...
 D is designed to be a simple language - easy to write a compiler for and
 easy to learn.
This does not mean it would be easy to program with it. Standard Pascal is
a
 very simple language, but it's very hard to write anything useful.
Very true. Pascal is a good language to learn how to write compilers. I can't say it's useful for much else. I am trying to bring my experience to bear on the problem of finding a fairly minimal set of features that cover most of the programming needs. I remember when Ada first appeared, it was considered unimplementable for years. Eventually, people did figure out how to implement it as compiler technology advanced. C++ also suffered for years being unimplementable. I wish to avoid that fate with D by at least providing source to a reference implementation. I read your comments with interest. Can I sum them up by saying that you wish for D to be more of a meta-language, such as providing the building blocks for dynamic arrays rather than implementing them directly? That's a valid point of view, and certainly the one C++ takes with STL. So why does D have dynamic arrays built in? 1) They are so darned useful. I use them everywhere in my own code - and find them to be a more than suitable replacement for most singly linked lists, doubly linked lists, stacks, queues, etc. Having to learn only dynamic arrays instead of vectors, lists, stacks, queues, etc., makes programming easier and less buggy. 2) By integrating them into the language, D can achieve tight and nearly seamless integration with static C style arrays - important for interfacing with external C functions. 3) Since the compiler knows about dynamic arrays, sensible and to the point error diagnostics can be issued, rather than the notoriously inscrutable messages coming from metalanguage constructs. 4) Good code can be generated for a builtin construct by a less sophisticated compiler. Constructs built up from meta-primitives usually need a very advanced compiler to generate comparably good code. 5) Designing the syntax into the language enables the use of special syntax where useful, such as the array slicing syntax. 6) In a garbage collected language, dynamic arrays should be a fundamental type, not something built up from metalanguage constructs. Metalanguage constructs are needed for special types, and should not be necessary for basic types.
Jul 19 2002
parent reply "Sean L. Palmer" <seanpalmer earthlink.net> writes:
"Walter" <walter digitalmars.com> wrote in message
news:ahaldu$ptj$1 digitaldaemon.com...
 "Andrey Tarantsov" <andreyvit nvkz.kuzbass.net> wrote in message
 news:aglpvi$qc0$1 digitaldaemon.com...
 D is designed to be a simple language - easy to write a compiler for
and
 easy to learn.
This does not mean it would be easy to program with it. Standard Pascal
is
 a
 very simple language, but it's very hard to write anything useful.
No object support, and no means to really control the display. No decent standard library. Yeah that makes it hard. There's also a bunch of practical extensions needed (Borland provided most of these later and became the de-facto standard).
 Very true. Pascal is a good language to learn how to write compilers. I
 can't say it's useful for much else. I am trying to bring my experience to
 bear on the problem of finding a fairly minimal set of features that cover
 most of the programming needs.
This is good, so long as we can extend the language later. If it will let us write really low level stuff that looks and acts like the things the language provides built-in.
 I remember when Ada first appeared, it was considered unimplementable for
 years. Eventually, people did figure out how to implement it as compiler
 technology advanced. C++ also suffered for years being unimplementable. I
 wish to avoid that fate with D by at least providing source to a reference
 implementation.

 I read your comments with interest. Can I sum them up by saying that you
 wish for D to be more of a meta-language, such as providing the building
 blocks for dynamic arrays rather than implementing them directly? That's a
 valid point of view, and certainly the one C++ takes with STL. So why does
D
 have dynamic arrays built in?

 1) They are so darned useful. I use them everywhere in my own code - and
 find them to be a more than suitable replacement for most singly linked
 lists, doubly linked lists, stacks, queues, etc. Having to learn only
 dynamic arrays instead of vectors, lists, stacks, queues, etc., makes
 programming easier and less buggy.
But the performance characteristics of dynamic arrays don't match those of lists. Yeah, you *can* build any container type out of some other container type, but the fundamental containers (vector, list) have vastly different performance characteristics and can't easily emulate one another without being very inefficient. Lists are for fast arbitrary insertion and removal and linear traversal. Arrays are for fast random access or linear traversal and are easier to copy since the whole thing can be copied as a contiguous block. Insertion at the end isn't too bad but can cause reallocations, insertion or removal at the beginning are very slow.
 2) By integrating them into the language, D can achieve tight and nearly
 seamless integration with static C style arrays - important for
interfacing
 with external C functions.
This is nice.
 3) Since the compiler knows about dynamic arrays, sensible and to the
point
 error diagnostics can be issued, rather than the notoriously inscrutable
 messages coming from metalanguage constructs.
Heh. Good point. ;)
 4) Good code can be generated for a builtin construct by a less
 sophisticated compiler. Constructs built up from meta-primitives usually
 need a very advanced compiler to generate comparably good code.
Agreed.
 5) Designing the syntax into the language enables the use of special
syntax
 where useful, such as the array slicing syntax.
Yes.
 6) In a garbage collected language, dynamic arrays should be a fundamental
 type, not something built up from metalanguage constructs. Metalanguage
 constructs are needed for special types, and should not be necessary for
 basic types.
Agreed, the most basic of basic types should be part of the language. They're so basic that everyone will have to implement them anyway or that they'll need to be part of the standard library. I think we should take another look at the possibility of adding linked lists directly to the language and formalizing the concept of iterator as a basic language feature. Can this be done? If so, how? I'm going to split this off into a new thread. Sean
Jul 20 2002
parent "Walter" <walter digitalmars.com> writes:
"Sean L. Palmer" <seanpalmer earthlink.net> wrote in message
news:ahcipd$4tg$1 digitaldaemon.com...
 "Walter" <walter digitalmars.com> wrote in message
 news:ahaldu$ptj$1 digitaldaemon.com...
So why does D
 have dynamic arrays built in?

 1) They are so darned useful. I use them everywhere in my own code - and
 find them to be a more than suitable replacement for most singly linked
 lists, doubly linked lists, stacks, queues, etc. Having to learn only
 dynamic arrays instead of vectors, lists, stacks, queues, etc., makes
 programming easier and less buggy.
But the performance characteristics of dynamic arrays don't match those of lists. Yeah, you *can* build any container type out of some other
container
 type, but the fundamental containers (vector, list) have vastly different
 performance characteristics and can't easily emulate one another without
 being very inefficient.
Yes, they are very different for long lists and long arrays. 99% of the time, however, I find that I have just a handful of members, and the performance difference just doesn't come up on the radar screen.
 I think we should take another look at the possibility of adding linked
 lists directly to the language and formalizing the concept of iterator as
a
 basic language feature.  Can this be done?  If so, how?

 I'm going to split this off into a new thread.
Ok, see ya there.
Jul 20 2002
prev sibling next sibling parent reply Toyotomi <kaishaku13 hotmail.com> writes:
I use Delphi and C++, Borland and Microsoft's


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...


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
Jul 11 2002
next sibling parent Toyotomi <kaishaku13 hotmail.com> writes:
well, but that's secondary to the fact that C is like a compiled Java.
Typo... D is like a compiled Java, not C... ;-p
Jul 11 2002
prev sibling parent reply "OddesE" <OddesE_XYZ hotmail.com> writes:
"Toyotomi" <kaishaku13 hotmail.com> wrote in message
news:bekriu4v4rm3ki1k7ip1n8071b9dmrfsct 4ax.com...
 I use Delphi and C++, Borland and Microsoft's


 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...


 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
I had a look at it and it's pretty nice! The language looks a lot like C/C++, but the environment starts to look more and more like Delphi. They have a great class library and the visual development environment is good too, some things that were seriously lacking in MSVC. By the way, what about Borland C++ Builder? Would that be something for you? JIT-compiled), but you can also just compile it straight to .dll's or .exes, so it is not as much as Java as is often said on this newsgroup. A collegea of mine is doing a about the possibilities. He likes it a lot. -- Stijn OddesE_XYZ hotmail.com http://OddesE.cjb.net _________________________________________________ Remove _XYZ from my address when replying by mail
Jul 13 2002
parent reply Toyotomi <kaishaku13 hotmail.com> writes:
On Sat, 13 Jul 2002 22:36:45 +0200, "OddesE" <OddesE_XYZ hotmail.com>
wrote:


I had a look at it and it's pretty nice! The
language looks a lot like C/C++, but the
environment starts to look more and more like
Delphi. They have a great class library and
the visual development environment is good too,
some things that were seriously lacking in
MSVC. By the way, what about Borland C++ Builder?
Would that be something for you?
it is like Java, and it is not like a self sufficient C/C++/Delphi app. The runtime and memory use is insanely larger, and it will never be the same thing. In order of frequency I use Delphi, C++ Builder & Visual Studio... However, after that are a slew of other languages and tools.
Jul 14 2002
parent reply "OddesE" <OddesE_XYZ hotmail.com> writes:
"Toyotomi" <kaishaku13 hotmail.com> wrote in message
news:e7j4ju49poihi6br27eqsgi4hv7vdl256s 4ax.com...


 it is like Java, and it is not like a self sufficient C/C++/Delphi app.
 The runtime and memory use is insanely larger, and it will never be the
 same thing.

 In order of frequency I use Delphi, C++ Builder & Visual Studio...
 However, after that are a slew of other languages and tools.
Well, you certainly seem to have a lot more experience with it than me. I guess I was misinformed. Sorry about that. So there really *is* a gap in the market for D. I thought you could straight compile your programs too. -- Stijn OddesE_XYZ hotmail.com http://OddesE.cjb.net _________________________________________________ Remove _XYZ from my address when replying by mail
Jul 16 2002
next sibling parent "anderson" <anderson firestar.com.au> writes:
"OddesE" <OddesE_XYZ hotmail.com> wrote in message
news:ah1b24$1iko$1 digitaldaemon.com...
 "Toyotomi" <kaishaku13 hotmail.com> wrote in message
 news:e7j4ju49poihi6br27eqsgi4hv7vdl256s 4ax.com...

estate

but
 it is like Java, and it is not like a self sufficient C/C++/Delphi app.
 The runtime and memory use is insanely larger, and it will never be the
 same thing.

 In order of frequency I use Delphi, C++ Builder & Visual Studio...
 However, after that are a slew of other languages and tools.
Well, you certainly seem to have a lot more experience with it than me. I guess I was misinformed. Sorry about that. So there really *is* a gap in the market for D. I thought you could straight compile your programs too.
You can "straight compile your programs", but I'm told that COM makes it slow. I'll b't there's still a JITC still working on some of the compoents.
 --
 Stijn
 OddesE_XYZ hotmail.com
 http://OddesE.cjb.net
 _________________________________________________
 Remove _XYZ from my address when replying by mail
Jul 16 2002
prev sibling parent reply "Walter" <walter digitalmars.com> writes:
"OddesE" <OddesE_XYZ hotmail.com> wrote in message
news:ah1b24$1iko$1 digitaldaemon.com...
 Well, you certainly seem to have a lot more experience
 with it than me. I guess I was misinformed. Sorry about
 that. So there really *is* a gap in the market for D. I

 thought you could straight compile your programs too.
machine code. This has a lot of interesting ramifications, from subtleties of the language design to how a resulting app looks. For example, you can
Jul 19 2002
parent reply "Steven Shaw" <steven_shaw iprimus.com.au> writes:
"Walter" <walter digitalmars.com> wrote in message
news:ahahse$mn4$1 digitaldaemon.com...

into
 machine code. This has a lot of interesting ramifications, from subtleties
 of the language design to how a resulting app looks. For example, you can

"system apps". I'm thinking device drivers. Could anyone provide me with other examples? Are there aspects of D other than it's ability to do inline assembly that lends D to systems programming? Apologies - I don't know much about systems programming. Why is it that device drivers need to be written in assembler? -- Regards, Steve.
Jul 20 2002
parent reply "Walter" <walter digitalmars.com> writes:
"Steven Shaw" <steven_shaw iprimus.com.au> wrote in message
news:ahcv9a$hhg$1 digitaldaemon.com...
 "system apps". I'm thinking device drivers. Could anyone provide me with
 other examples?
Most of the operating system can be called a "system app". System apps include compilers, editors, utilities, networking infrastructure code, the Java VM, the .net VM, etc.
 Are there aspects of D other than it's ability to do inline assembly that
 lends D to systems programming?
Yes: 1) it can be compiled to machine code and stored as an executable binary 2) it doesn't require an abstraction layer or virtual machine between it and the actual hardware 3) it can interface directly to the raw operating system entry points 4) type checking, semantic analysis, etc., is done at compile time, not run time, so the executable code runs at maximal speed with minimal overhead 5) the semantics of the language are flexible enough to conform to the actual peculiarities of real CPUs, so no costly and slow emulations are necessary
 Apologies - I don't know much about systems programming. Why is it that
 device drivers need to be written in assembler?
They don't always need to be written in assembler - but frequently there are special instructions that need to be executed, I/O ports that need accessing, interrupt handlers that need hooking, etc., and those usually get done with a bit of assembler. Inline assembler can also get you out of a hole when the compiler is not generating good enough code for a particular performance bottleneck.
Jul 20 2002
parent reply "Steven Shaw" <steven_shaw iprimus.com.au> writes:
"Walter" <walter digitalmars.com> wrote in message
news:ahd42a$lt8$1 digitaldaemon.com...
 "Steven Shaw" <steven_shaw iprimus.com.au> wrote in message
 news:ahcv9a$hhg$1 digitaldaemon.com...
 "system apps". I'm thinking device drivers. Could anyone provide me with
 other examples?
Most of the operating system can be called a "system app". System apps include compilers, editors, utilities, networking infrastructure code, the Java VM, the .net VM, etc.
Just to clarify: .net doesn't have a VM. It's just got a runtime. Microsoft calls it CLR for .net and CLI in the ecma spec Common Language Runtime (or Infrastructure I think). I get what you mean. Modula-3 was a language, too that was design to be used for systems programming but still had modules, class-based objects and gc.
 Are there aspects of D other than it's ability to do inline assembly
that
 lends D to systems programming?
Yes: 1) it can be compiled to machine code and stored as an executable binary
For some embedded work this is probably mandatory. I get the feeling, though, that many system apps do not require this feature. Though it doesn't hurt to have it. newsgroup. You can write compilers, editors, jvm's in Java (can't say I know *how* they did it), so I'm sure that it would be pretty hard to come up with a task that just flat can't be done.
 2) it doesn't require an abstraction layer or virtual machine between it
and
 the actual hardware
Does this mean that D doesn't have a runtime? Or more likely that you can optionally leave out the runtime at link time?
 3) it can interface directly to the raw operating system entry points
Is this the C interoperability at work?
 4) type checking, semantic analysis, etc., is done at compile time, not
run
 time, so the executable code runs at maximal speed with minimal overhead
I also get the feeling from other posts that the D implementation uses whole program optimisation techniques to decide when methods need not be dynamically dispatched. yes?
 5) the semantics of the language are flexible enough to conform to the
 actual peculiarities of real CPUs, so no costly and slow emulations are
 necessary
Understood. More like C (than Java) in this respect.
 Apologies - I don't know much about systems programming. Why is it that
 device drivers need to be written in assembler?
They don't always need to be written in assembler - but frequently there
are
 special instructions that need to be executed, I/O ports that need
 accessing, interrupt handlers that need hooking, etc., and those usually
get
 done with a bit of assembler. Inline assembler can also get you out of a
 hole when the compiler is not generating good enough code for a particular
 performance bottleneck.
Thanks. This is starting to ring some old bells from school days. In a C project I once saw inline assembler used to access the host cpu's test-and-set operation(s) for implementing locks. Until then I didn't think you could embed asm in C (maybe just a gcc enhancement). --Cheers, Steve.
Jul 21 2002
next sibling parent Pavel Minayev <evilone omen.ru> writes:
On Sun, 21 Jul 2002 18:27:08 +1000 "Steven Shaw" <steven_shaw iprimus.com.au> 
wrote:

 For some embedded work this is probably mandatory. I get the feeling,
 though, that
 many system apps do not require this feature. Though it doesn't hurt to have
 it.

 newsgroup.
 You can write compilers, editors, jvm's in Java (can't say I know *how* they
 did it), so
 I'm sure that it would be pretty hard to come up with a task that just flat
 can't be done.
You can write GUI applications in Java, but do they work fast? And how would they work if entire graphics output, down to the lowest-level primitives, would be written in Java? VM... not sure how fast VM written in Java would be, but I'd bet it is slower than any VM written in some non-interpreted language.
 2) it doesn't require an abstraction layer or virtual machine between it
and
 the actual hardware
Does this mean that D doesn't have a runtime?
It does, but it is embedded into your executable. You don't need any external applications or DLLs or components to run the D program. For Java, you need
 Or more likely that you can optionally leave out the runtime at link time?
I doubt. GC, dynamic arrays, hashes, class Object, ClassInfo - are all in RTL.
 3) it can interface directly to the raw operating system entry points
Is this the C interoperability at work?
Not only C, but also stdcall.
 I also get the feeling from other posts that the D implementation uses whole
 program optimisation techniques to decide when methods need not be
 dynamically dispatched. yes?
It is stated. But I'm not sure whether current alpha supports this.
 Thanks. This is starting to ring some old bells from school days.
 In a C project I once saw inline assembler used to access the host cpu's
 test-and-set operation(s) for implementing locks. Until then I didn't think
 you could embed asm in C (maybe just a gcc enhancement).
It isn't ANSI C (nor C++), but I haven't yet seen any C/C++ compiler which doesn't support some form of inline asm. At least MS, Intel, Borland, GNU, and DM compilers support it.
Jul 21 2002
prev sibling parent reply "Walter" <walter digitalmars.com> writes:
"Steven Shaw" <steven_shaw iprimus.com.au> wrote in message
news:ahdqvg$1cru$1 digitaldaemon.com...
 "Walter" <walter digitalmars.com> wrote in message
 news:ahd42a$lt8$1 digitaldaemon.com...
 Just to clarify: .net doesn't have a VM. It's just got a runtime.
Microsoft
 calls it CLR for .net
 and CLI in the ecma spec Common Language Runtime (or Infrastructure I
 think).
ready to run app), I need the VM, CLR, or CLI which is (correct me if I'm wrong) over 10 megabytes of memory. That may not be so important in the future, but it is now.
 For some embedded work this is probably mandatory. I get the feeling,
 though, that
 many system apps do not require this feature. Though it doesn't hurt to
have
 it.
Correct, you can write systems apps that don't use inline assembler, but the more sophisticated and commercially successful ones generally do.

 newsgroup.
 You can write compilers, editors, jvm's in Java (can't say I know *how*
they
 did it), so
I took the Java compiler written in Java and translated it to C++. It ran ten times faster.
 I'm sure that it would be pretty hard to come up with a task that just
flat
 can't be done.
Sure, it's less of an issue of can/cannot be done, but how practical it is.
 2) it doesn't require an abstraction layer or virtual machine between it
and
 the actual hardware
Does this mean that D doesn't have a runtime? Or more likely that you can optionally leave out the runtime at link time?
D does have a runtime, but it is pretty minimal at 40k rather than multiple megabytes. The runtime can also be bypassed for special apps. One other conceptual difference is that D apps do not run under the control of the app. D apps do not run in a sandbox created by the runtime, and D apps can do every down and dirty programming trick if you really want to use them.
 3) it can interface directly to the raw operating system entry points
Is this the C interoperability at work?
need to create a DLL with wrappers, and you need to do considerable translation for passing other than the most basic types.
 4) type checking, semantic analysis, etc., is done at compile time, not
run
 time, so the executable code runs at maximal speed with minimal overhead
I also get the feeling from other posts that the D implementation uses
whole
 program optimisation techniques to decide when methods need not be
 dynamically dispatched. yes?
D can do this, although the current implementation does not.
Jul 21 2002
parent reply "Steven Shaw" <steven_shaw iprimus.com.au> writes:
"Walter" <walter digitalmars.com> wrote in message
news:ahf57o$2j1a$1 digitaldaemon.com...
 "Steven Shaw" <steven_shaw iprimus.com.au> wrote in message
 news:ahdqvg$1cru$1 digitaldaemon.com...
 "Walter" <walter digitalmars.com> wrote in message
 news:ahd42a$lt8$1 digitaldaemon.com...
 Just to clarify: .net doesn't have a VM. It's just got a runtime.
Microsoft
 calls it CLR for .net
 and CLI in the ecma spec Common Language Runtime (or Infrastructure I
 think).
ready to run app), I need the VM, CLR, or CLI which is (correct me if I'm wrong) over 10 megabytes of memory. That may not be so important in the future, but it is now.
I don't know how much memory the CLR takes up. I think the embedded version is being worked on.
 *snip*


 newsgroup.
 You can write compilers, editors, jvm's in Java (can't say I know *how*
they
 did it), so
I took the Java compiler written in Java and translated it to C++. It ran ten times faster.
Typical jvms has this lazy compilation of methods which I think is not such a great idea. This could have been a large part of the time taken. To see what a difference it makes you could use something like beanshell, run the compiler once to ensure it is compiled and then again to measure. It would be interesting to see how the results differ when using gcj. I can see, though, that with D, you don't have to worry about startup speed. as it is with Java/JVM.
 I'm sure that it would be pretty hard to come up with a task that just
flat
 can't be done.
Sure, it's less of an issue of can/cannot be done, but how practical it
is. Sure.
 2) it doesn't require an abstraction layer or virtual machine between
it
 and
 the actual hardware
Does this mean that D doesn't have a runtime? Or more likely that you can optionally leave out the runtime at link
time?
 D does have a runtime, but it is pretty minimal at 40k rather than
multiple
 megabytes. The runtime can also be bypassed for special apps. One other
 conceptual difference is that D apps do not run under the control of the

 app. D apps do not run in a sandbox created by the runtime, and D apps can
 do every down and dirty programming trick if you really want to use them.
I'm not sure what you're getting at here. Could you please provide an example?
 3) it can interface directly to the raw operating system entry points
Is this the C interoperability at work?
you
 need to create a DLL with wrappers, and you need to do considerable
 translation for passing other than the most basic types.
This is something that really makes D different. I really hate JNI wrappers. CLR has platform invoke but I don't know enough to comment on it.
 4) type checking, semantic analysis, etc., is done at compile time,
not
 run
 time, so the executable code runs at maximal speed with minimal
overhead
 I also get the feeling from other posts that the D implementation uses
whole
 program optimisation techniques to decide when methods need not be
 dynamically dispatched. yes?
D can do this, although the current implementation does not.
This could be hard/impossible to achieve in the face of dynamic loading. Java implementations can handle this at runtime, purging native code when dynamic loading causes invalidation of a this optimisation. purged when assemblies are loaded at runtime, too but I don't think the current implementations do it that way. I like D. A smallish, fast to compile, fast to execute, modular, java-style oo, gc'ed language. like them all. --Cheers, Steve.
Jul 21 2002
parent reply "Walter" <walter digitalmars.com> writes:
"Steven Shaw" <steven_shaw iprimus.com.au> wrote in message
news:ahg4lr$g45$1 digitaldaemon.com...
 "Walter" <walter digitalmars.com> wrote in message
 news:ahf57o$2j1a$1 digitaldaemon.com...
 I took the Java compiler written in Java and translated it to C++. It
ran
 ten times faster.
Typical jvms has this lazy compilation of methods which I think is not
such
 a great idea.
 This could have been a large part of the time taken. To see what a
 difference it
 makes you could use something like beanshell, run the compiler once to
 ensure
 it is compiled and then again to measure. It would be interesting to see
how
 the results differ when using gcj.
Why it was faster in C++ is a complicated matter, it's more than just startup time. And no, it wasn't the garbage collector <g>.
 D does have a runtime, but it is pretty minimal at 40k rather than
multiple
 megabytes. The runtime can also be bypassed for special apps. One other
 conceptual difference is that D apps do not run under the control of the

 app. D apps do not run in a sandbox created by the runtime, and D apps
can
 do every down and dirty programming trick if you really want to use
them.
 I'm not sure what you're getting at here. Could you please provide an
 example?
For example, you can write a garbage collector in D. There is no way to do it in Java - the type checking and the sandbox will prevent it.
 This could be hard/impossible to achieve in the face of dynamic loading.
Yes, but currently D is not defined to deal with dynamic loading. <g>
 I like D. A smallish, fast to compile, fast to execute, modular,
java-style
 oo,  gc'ed language.

 like them all.
They each have their place. D is not targetted at what Java is, so the design tradeoffs are different. Using D for what Java is best at is inappropriate, and vice versa.
Jul 22 2002
parent reply "Juan Carlos Arevalo Baeza" <jcab roningames.com> writes:
"Walter" <walter digitalmars.com> wrote in message
news:ahgfa7$sgf$1 digitaldaemon.com...

 This could be hard/impossible to achieve in the face of dynamic loading.
Yes, but currently D is not defined to deal with dynamic loading. <g>
But it will at some point, won't it? ;-) Salutaciones, JCAB
Jul 22 2002
parent reply "Walter" <walter digitalmars.com> writes:
"Juan Carlos Arevalo Baeza" <jcab roningames.com> wrote in message
news:ahk5pu$2ao$1 digitaldaemon.com...
 "Walter" <walter digitalmars.com> wrote in message
 news:ahgfa7$sgf$1 digitaldaemon.com...
 This could be hard/impossible to achieve in the face of dynamic
loading.
 Yes, but currently D is not defined to deal with dynamic loading. <g>
But it will at some point, won't it? ;-)
I'm not sure how that would work out.
Jul 23 2002
next sibling parent "Juan Carlos Arevalo Baeza" <jcab roningames.com> writes:
"Walter" <walter digitalmars.com> wrote in message
news:ahk9fv$1b1h$1 digitaldaemon.com...

 Yes, but currently D is not defined to deal with dynamic loading. <g>
But it will at some point, won't it? ;-)
I'm not sure how that would work out.
You'd need to provide a way to express the binary interface of the DLL. For example, inhibiting inheritance from specific classes outside of the DLL where they reside would get you a large portion of the way there. In general, the interface would somehow be: - List of classes that are abstract from outside the DLL. Useful for handle-style APIs. - List of classes, variables and functions that are publicly accessible from outside the DLL. - List of classes that are also inheritable from outside the DLL. Now, you can optimize the hell out of everything in the DLL, except those classes you can inherit from. Salutaciones, JCAB
Jul 24 2002
prev sibling parent "anderson" <anderson firestar.com.au> writes:
"Walter" <walter digitalmars.com> wrote in message
news:ahk9fv$1b1h$1 digitaldaemon.com...
 "Juan Carlos Arevalo Baeza" <jcab roningames.com> wrote in message
 news:ahk5pu$2ao$1 digitaldaemon.com...
 "Walter" <walter digitalmars.com> wrote in message
 news:ahgfa7$sgf$1 digitaldaemon.com...
 This could be hard/impossible to achieve in the face of dynamic
loading.
 Yes, but currently D is not defined to deal with dynamic loading. <g>
But it will at some point, won't it? ;-)
I'm not sure how that would work out.
I'd like it to compile/load C style DLL's and simply have a handle attached to each method (or as a state machine) for classes. That way you could DLL write code in C (or C++ interfaced by C) and use it in D dynamicly. Also you could write a DLL in D and use it dynamicly in C. Parhaps exceptions could be used to test if functions exist. It's annoying having to type the same code over and over in C to simply test and extract all the functions from a DLL in C. Parhaps D could also complie a sample dynamic loading code with all the funcion/methods defintions included or one better, create a .d file that does it for that file. Parhaps for classes it may look something like: class eatMe : mouth; loadDLibrary(Filename, eatME); eatME Object; //But that'll need more work. And a for a function list (called functionList) DLL with a pre-produced .d file (functionlist.d). import functionlist; loadFunctionList(Filename); //Of course that would only allow one set of functionList, but classes should generaly be used for more the one anyway. Besides parhaps they could be indexed using a state machine type structure. setFunctionList(int Index); //Index to the current set of functions Of course there's the other side to look at: Parhaps for classes... dll class eatME : mouth { ... } and functions dll void func() { ... } These are just a starting point, and probably need alot of work.
Jul 24 2002
prev sibling parent reply "Sean L. Palmer" <seanpalmer earthlink.net> writes:
Up front:  I agree with much of what you say.

"Таранцов Андрей" <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.)
I have only designed 2 languages (both script compilers)
 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.
I once worked with an ex-marine on a Borland Pascal project. He used to go on about ADA, but I never researched it much as it's not used much in day-to-day applications outside military circles. Hard to find a compiler for. ;)
 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 agree to some extent. I think D's major shortcoming is its ancestry from C. That's also a perk, albeit one I personally don't need or want. D doesn't have many of the nice things about Pascal (ranges, sets) but it does have many others (strings (darray of char), units (modules), module header files!!!, no forward declarations!!!, GC) while retaining some of C's power (pointers, nice operators for basic types, and low-level programming) All these languages have their good and bad points. One could do much much worse than to just combine all the good points. ;)
 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:
I do agree that the language should attempt to make it possible to write your own "basic types" such as complex, quaternion, tensor, string, list, hashmap, whatever, all the way up through simple quick utility programs up through gigantic government database programs and missile guidance software and everything in between. A programming language should be a toolset for building programs out of small parts. The smaller the basic parts, the better... up to a point. The dividing point is where the compiler can't figure out what it is that you're doing well enough to write optimal code. So a few very low level features such as dynamic arrays are nice to have builtin to the language because (A) you don't have to write them yourself; you can always depend on them being available (B) you don't have to debug them, or step through or over them while debugging higher-level code, (C) the compiler knows what it is and can generate much better code than if it had to reverse-engineer the intent from your source code. Also builtin types have a few advantages currently since there are no templates or operator overloading (yet!) it would not be possible to write a good darray at all in D yet. I advocate putting the tools needed to build new low-level types into the language. Those are: generics, operator overloading, forced inlining, forced constant folding. Introspection would help make generics easier. Unification of handling of builtin and user-defined types would also be a godsend. This is something that really can't wait for version 2.0 because introducing generics will change the language enough to invalidate all code written to the D 1.0 spec. Also I doubt it will gain major following until generics are supported.
 -> 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.
I'd rather have alloca() and some kind of generic user-definable factory or allocator scheme than GC. GC isn't a perfect solution for memory management any more than refcounting is. At least it's safer than explicit malloc/free all over the place.
 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? ;)
And quaternions, and matrices, column/row vectors, geometric algebra, fixed point, big number, date, time, color, polygon, SIMD register types, etc, etc, etc. Gotta draw the line somewhere. I'd rather have language support for building my own basic types and enough tools and hints to the compiler that I can write a class that runs as efficiently as anything the compiler could generate.
 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.
It's based off C, not C++.
 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).
Syntax *does* matter. A LOT. Syntax is what I despised about Pascal the most. Syntax is one of the major problems with C and C++. Syntax is why I can't stand 99% of all the wierd little experimental languages you see being invented in universities. Syntax will be a huge factor in influencing whether a language gains acceptance from the masses.
 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.
This is typedef in D. But D doesn't support ranges at all. ;(
 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
Compiler should be able to figure this out for itself.
 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.
That pascalesque syntax and whatever those apostrophe clauses are don't sit well with me.
 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
interesting (although it's going to get software emulation if you go past precision of extended)
 type Fixed_Point_Dollars is range -10 ** 10 .. 10 ** 10 delta 0.01; --
Fixed
 point aka "Currency" type
Now this is really really cool. ;)
 There is a "modulus" type like this:

 type Byte is mod 256; -- 255 + 1 = 0; 10 - 12 = 253, and so on
So you can declare bounded types and wrapping types. But can you declare saturating types?
 type Wow is mod 7; -- useful for indexes: 6 + 1 = 0; 0 - 2 = 3.
Sounds really slow. Could occasionally be useful.
 2. Generics. Ada generics are the best! ;) But, they must be instanciated
 explicitly. Like this:

 generic
     type Index is (<>); -- Index is any *discrete* type
What kind of wierd syntax is this?
     type Elem is private; -- Elem is any fixed-size type supporting "="
and
 assignment
If you ask me (and you didn't) I'd want to be able to completely hide any private members from other code. Other code shouldn't even know the private members exist. Which means you need to be able to specify them from outside the externally visible declaration. // visible interface class Foo_public : private Foo_private { void GoForIt(); } // hidden somewhere protected except(Foo_public) class Foo_private { int myprivateint; // nobody can see this but Foo_public }
     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 ;)

 ...
I can't follow that syntax.
 type Int_Array is array (Natural range 0 .. 20) of Integer;
 procedure Sort is new Generic_Sort (Int_Array'Domain, Integer, Int_Array);
What's with the apostophe operator?
 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?
As long as ADA has been around, there must be something seriously wrong with it if nobody has developed a GUI library for it yet.
 3. Packages. They are like this:

 -- in Foo.ads
 package Foo is
     -- public part
 private
     -- private part
 end Foo;
This is what I disagree with. For one thing, the public and private sections can get to be HUGE. I like D's attribute style. And ideally you wouldn't "declare" anything that's supposed to be private. Nobody outside needs to know it exists.
 -- 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;
Linked lists are such a basic data type it should be builtin to the language. Programmers hate having to reimplement list adding and list walking every time they need a list, and it's error prone. Pointers (necessary to implement a linked list) are just too dangerous to leave laying around for some unsuspecting maintenance programmer to shoot themselves in the foot with. But linked lists are FUNDAMENTAL and necessary and should be in the language.
 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.
That's what an IDE is for. I don't want D language spec to even have any clue that there are any such thing as .D files.
 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.
It has separate compilation; haven't you tried it at all before making wild claims? Of course you cannot declare a class in one module and put its implementation in a different module. So when it compiles the class it does indeed know all that's necessary to generate code. If it cannot know for some reason (templates or inline functions used in other modules) then it may have to generate code at link time.
 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!
I also would beg to differ. C++ isn't exactly what I'd call elegant. It's nifty, sure. But it's a behemoth. The 900 pound gorilla of programming languages. Sean
Jul 11 2002
next sibling parent "anderson" <anderson firestar.com.au> writes:
 What's with the apostophe operator?

 Sean
It's simular to D's property syntax. ( ' instead of . )
Jul 12 2002
prev sibling next sibling parent reply "OddesE" <OddesE_XYZ hotmail.com> writes:
"Sean L. Palmer" <seanpalmer earthlink.net> wrote in message
news:aglttj$uan$1 digitaldaemon.com...
<SNIP>
 If you ask me (and you didn't) I'd want to be able to completely hide any
 private members from other code.  Other code shouldn't even know the
private
 members exist.  Which means you need to be able to specify them from
outside
 the externally visible declaration.

 // visible interface

 class Foo_public : private Foo_private
 {
     void GoForIt();
 }

 // hidden somewhere

 protected except(Foo_public)
 class Foo_private
 {
     int myprivateint; // nobody can see this but Foo_public
 }
<SNIP>
 Sean
So use interfaces: interface IFoo { void GoForIt(); } class Foo: Object, IFoo { int myprivateint; void GoForIt() { printf ("myprivateint==%d\n", myprivateint); } } Then you only need to publish the interface and can keep everything else private. -- Stijn OddesE_XYZ hotmail.com http://OddesE.cjb.net _________________________________________________ Remove _XYZ from my address when replying by mail
Jul 13 2002
parent reply "Sean L. Palmer" <seanpalmer earthlink.net> writes:
That forces everything to be virtual.

But yeah it would work unless you wanted to have data in the public
interface.

What I want really is to be able to avoid having to use pImpl pattern as is
necessary to really hide the guts of a class in C++.  This may already be
mostly possible in D;  probably is.

Sean

"OddesE" <OddesE_XYZ hotmail.com> wrote in message
news:agq3mj$b41$1 digitaldaemon.com...
 "Sean L. Palmer" <seanpalmer earthlink.net> wrote in message
 news:aglttj$uan$1 digitaldaemon.com...
 <SNIP>
 If you ask me (and you didn't) I'd want to be able to completely hide
any
 private members from other code.  Other code shouldn't even know the
private
 members exist.  Which means you need to be able to specify them from
outside
 the externally visible declaration.

 // visible interface

 class Foo_public : private Foo_private
 {
     void GoForIt();
 }

 // hidden somewhere

 protected except(Foo_public)
 class Foo_private
 {
     int myprivateint; // nobody can see this but Foo_public
 }
<SNIP>
 Sean
So use interfaces: interface IFoo { void GoForIt(); } class Foo: Object, IFoo { int myprivateint; void GoForIt() { printf ("myprivateint==%d\n", myprivateint); } } Then you only need to publish the interface and can keep everything else private. -- Stijn OddesE_XYZ hotmail.com http://OddesE.cjb.net _________________________________________________ Remove _XYZ from my address when replying by mail
Jul 13 2002
parent "OddesE" <OddesE_XYZ hotmail.com> writes:
"Sean L. Palmer" <seanpalmer earthlink.net> wrote in message
news:agq42d$bb6$1 digitaldaemon.com...
 That forces everything to be virtual.
In D all method pointers are already virtual aren't they?
 But yeah it would work unless you wanted to have data in the public
 interface.

 What I want really is to be able to avoid having to use pImpl pattern as
is
 necessary to really hide the guts of a class in C++.  This may already be
 mostly possible in D;  probably is.

 Sean
Yeah, when I first learned that private fields need to be in the .h file in C++ I thought it really sucked too! They should have something like int CMyClass::myfield; in the .cpp files, where CMyClass would be a class declared in a header file included by the .cpp file. This should also go for methods. If they only exist in the .cpp file, they are automatically private. -- Stijn OddesE_XYZ hotmail.com http://OddesE.cjb.net _________________________________________________ Remove _XYZ from my address when replying by mail
Jul 14 2002
prev sibling parent reply "anderson" <anderson firestar.com.au> writes:
 If you ask me (and you didn't) I'd want to be able to completely hide any
 private members from other code.  Other code shouldn't even know the
private
 members exist.  Which means you need to be able to specify them from
outside
 the externally visible declaration.
Yes, I never understood why C++ kept privates visible in the header. D automatically generates a header file, perhaps they could be removed from that. If it is useful to have a private member listing, they could be placed in another file.
Jul 13 2002
parent reply "Andrey Tarantsov" <andreyvit nvkz.kuzbass.net> writes:
Hello.

 Yes, I never understood why C++ kept privates visible in the header. D
 automatically generates a header file, perhaps they could be removed from
 that.  If it is useful to have a private member listing, they could be
 placed in another file.
I don't understand all of you. Private data *must* be visible to the world, because compilers must know how much memory to allocate for your classes. C++ does not use reference symantics, neither does Ada. But Ada allows you to define everything you want to be private in the private section of the package (and in C++, like I've shown, something that should be private has to be public, and that is not good). Of course, nonvirtual private procedures can (and should) be declared in the body of the package, i.e., the world wan't know anything. Virtual procedures must be in the spec to know how many slots does your type occupy in the v-table. About exceptions: my example was not good. I did not meant that you should pass line & column no of exception. The exception was named EBadToken, and it was a part of some hypotetical lexical parser. LineNo and ColNo were just information that could be called FooData and BarData. The names do not matter. I said that was not a proposal because that was not a complete exception model. A proposal is something I think is suitable for the language, or at least one of the ways something might be implemented. And my code was just an example, to start a subject of exceptions. I think the idea of having numerous allocation methods is rather good. Again, first, look thru Ada Rationale - Ada has a convinient model of storage pools. I don't say D's "allocation methods" should look like Ada storage pools, but before creating something yourself, it's better to look through the existent implementations, determine what you like and what you don't like.
Jul 14 2002
next sibling parent "anderson" <anderson firestar.com.au> writes:
"Andrey Tarantsov" <andreyvit nvkz.kuzbass.net> wrote in message
news:agschk$2idc$1 digitaldaemon.com...
 Hello.

 Yes, I never understood why C++ kept privates visible in the header. D
 automatically generates a header file, perhaps they could be removed
from
 that.  If it is useful to have a private member listing, they could be
 placed in another file.
I don't understand all of you. Private data *must* be visible to the
world,
 because compilers must know how much memory to allocate for your classes.
An intelligent compiler can append the private members from the body file before compliation. Java does this. From a users point of view, private's is just space junk because they can't use it. Ada had the same problem.
Of course, nonvirtual private procedures can (and should) be declared in
the body of the package. When would you ever get a virtual private?
Jul 14 2002
prev sibling parent "Sean L. Palmer" <seanpalmer earthlink.net> writes:
"Andrey Tarantsov" <andreyvit nvkz.kuzbass.net> wrote in message
news:agschk$2idc$1 digitaldaemon.com...
 Hello.

 Yes, I never understood why C++ kept privates visible in the header. D
 automatically generates a header file, perhaps they could be removed
from
 that.  If it is useful to have a private member listing, they could be
 placed in another file.
I don't understand all of you. Private data *must* be visible to the
world,
 because compilers must know how much memory to allocate for your classes.
 C++ does not use reference symantics, neither does Ada. But Ada allows you
 to define everything you want to be private in the private section of the
 package (and in C++, like I've shown, something that should be private has
 to be public, and that is not good). Of course, nonvirtual private
 procedures can (and should) be declared in the body of the package, i.e.,
 the world wan't know anything. Virtual procedures must be in the spec to
 know how many slots does your type occupy in the v-table.
They should get such information from the linker. Code generation should go after link step. Or the compiler and linker could be otherwise integrated. You need this for templates anyway.
 About exceptions: my example was not good. I did not meant that you should
 pass line & column no of exception. The exception was named EBadToken, and
 it was a part of some hypotetical lexical parser. LineNo and ColNo were
just
 information that could be called FooData and BarData. The names do not
 matter.

 I said that was not a proposal because that was not a complete exception
 model. A proposal is something I think is suitable for the language, or at
 least one of the ways something might be implemented. And my code was just
 an example, to start a subject of exceptions.

 I think the idea of having numerous allocation methods is rather good.
 Again, first, look thru Ada Rationale - Ada has a convinient model of
 storage pools. I don't say D's "allocation methods" should look like Ada
 storage pools, but before creating something yourself, it's better to look
 through the existent implementations, determine what you like and what you
 don't like.
If to allocate an object you had to call some kind of per-class allocator instead of just requesting memory from wherever you want, this would be solved nicely. Is the extra flexibility really worth it? Perhaps a class could have multiple potential allocator pools (system memory, fast memory, or fixed sized preallocated buffer slot) Sean
Jul 15 2002