Jump to page: 1 26  
Page
Thread overview
D stack allocation
Aug 11, 2004
van eeshan
Aug 11, 2004
Andy Friesen
Aug 11, 2004
van eeshan
Aug 11, 2004
van eeshan
Aug 11, 2004
Sean Kelly <sean
Aug 11, 2004
stonecobra
Aug 11, 2004
van eeshan
Aug 11, 2004
Sean Kelly
Aug 12, 2004
Regan Heath
Aug 12, 2004
Walter
Aug 12, 2004
Walter
Aug 12, 2004
van eeshan
Aug 12, 2004
Derek Parnell
Aug 12, 2004
Ben Hinkle
Aug 12, 2004
van eeshan
Aug 12, 2004
Walter
Aug 12, 2004
van eeshan
Aug 13, 2004
Walter
Aug 13, 2004
Michael
Aug 13, 2004
Walter
Aug 13, 2004
Michael
Aug 13, 2004
van eeshan
Aug 13, 2004
Sean Kelly
Aug 13, 2004
Walter
Aug 13, 2004
van eeshan
Aug 13, 2004
van eeshan
Aug 13, 2004
Walter
Immovable arrays (was Re: D stack allocation)
Aug 13, 2004
Arcane Jill
Aug 13, 2004
Walter
Aug 13, 2004
Arcane Jill
Aug 13, 2004
Walter
Aug 13, 2004
van eeshan
Aug 13, 2004
Arcane Jill
Aug 13, 2004
van eeshan
Aug 13, 2004
Walter
Aug 30, 2004
van eeshan
Aug 12, 2004
Ilya Minkov
Aug 13, 2004
Ben Hinkle
Aug 13, 2004
Arcane Jill
Aug 13, 2004
Ben Hinkle
Aug 13, 2004
Andy Friesen
Aug 13, 2004
van eeshan
Aug 13, 2004
Andy Friesen
Aug 13, 2004
van eeshan
Aug 13, 2004
Andy Friesen
Aug 13, 2004
Ben Hinkle
The stack and the GC (was D stack allocation)
Aug 13, 2004
van eeshan
Aug 16, 2004
ben
Aug 16, 2004
Derek Parnell
Aug 13, 2004
van eeshan
Aug 11, 2004
Ben Hinkle
Aug 11, 2004
van eeshan
Aug 12, 2004
Ben Hinkle
Aug 12, 2004
Walter
Aug 12, 2004
van eeshan
Aug 12, 2004
Arcane Jill
Aug 12, 2004
van eeshan
Aug 13, 2004
van eeshan
August 11, 2004
"Walter" <newshound@digitalmars.com> wrote in message news:cfbip7$ora$1@digitaldaemon.com...
>
> "van eeshan" <vanee@hotmail.net> wrote in message news:cfb72j$9l7$1@digitaldaemon.com...
> > "Walter" <newshound@digitalmars.com> wrote in message news:cfb5v9$76u$1@digitaldaemon.com...
> > > The problem, however, is that since Java does not allow any objects or arrays on the stack (or in static data), whenever you need one it
needs
> to
> > > be allocated on the heap. This is a lot more expensive than stack allocation. Since one winds up allocating a lot more heap objects in
> Java
> > > than one does in C/C++, the end result is slower. Java offers no alternatives to gc allocation.
> > >
> > > This is why D allows stack based objects and value objects.
> >
> > Are you saying that D allows one to create Objects entirely upon the
> stack?
>
> For auto objects, it is allowed for the compiler to put them there. But I was primarilly referring to structs and arrays.
>
> > And entirely within static data?
>
> Structs and arrays, yes. Java does not allow structs, nor does it allow arrays on the stack.


Thanks for clarifying that Walter. Would it be prudent to note that D allocates auto Objects on the heap? Stack allocation may be allowed for in the spec, but that's not how the compiler operates.

Also, there is that point about heap allocations being a lot more expensive than stack allocations. Naturally, one would lean towards wholeheartedly agreeing; but this is just not true when it comes to D. Here's a little (contrived) test jig to illustrate:

private import std.c.time;
private import std.c.stdlib;
private import std.c.windows.windows;

void heap()
{
        void *x = malloc (16 * 1024);
        free (x);
}

void stack()
{
        ubyte[16 * 1024] x;
}

void trace (uint startTime)
{
        FILETIME ft;
        GetSystemTimeAsFileTime(&ft);
        printf ("%u\n", (ft.dwLowDateTime - startTime) / 10000);
}

void main()
{
        FILETIME start;

       GetSystemTimeAsFileTime(&start);
        trace (start.dwLowDateTime);

        sleep (3);
        trace (start.dwLowDateTime);

        for (int i=1_000_000; --i;)
             heap();

        trace (start.dwLowDateTime);

        for (int i=1_000_000; --i;)
             stack();

        trace (start.dwLowDateTime);
}

The results? On this machine it takes the heap() routine ~500ms to execute, and the stack() version ~3500ms. Yep, that's seven times longer. Why? What wasn't stated is that D ensures all stack variables are initialized ... including arrays. The innocuous stack allocation actually clears the 16KB to zero each time, which is why it takes so long. For a 32KB 'buffer', the stack() execution time goes up to ~8600ms versus the ~500ms for heap(); you can see there's some rather non-linear behavior for the stack version <g>

The point here is not about the benefits/detriments of deterministic initialization. It's about clarifying a point of performance-tuning that is far from obvious. Without wishing to put too fine a point on it, the quoted post was somewhat misleading. That is; allocating an array on the D stack can consume far more cycles than the equivalent heap allocation. It depends upon the size of the array, the bus speed, the size of the cache, heap fragmentation and many other things.

D stack allocations are simply not like C/C++ at all. Far from it.


For the curious, here's the disassembly for both routines. It's worth noting that the array initialization could be sped up. Also worth noting is that the loop/call overhead was 10ms.

10:   {
11:           void *x = malloc (16 * 1024);
12:           free (x);
00402011   push        4000h
00402016   call        _malloc (0040574c)
0040201B   add         esp,4
0040201E   push        eax
0040201F   call        _free (004057a4)
00402024   add         esp,4
13:   }
00402027   pop         eax
00402028   ret
14:
15:
16:   void stack()
0040202C   push        ebp
0040202D   mov         ebp,esp
0040202F   mov         edx,4
00402034   sub         esp,1000h
0040203A   test        dword ptr [esp],esp
0040203D   dec         edx
0040203E   jne         _D5hello5stackFZv+8 (00402034)
00402040   sub         esp,edx
00402042   mov         ecx,4000h
00402047   xor         eax,eax
17:   {
18:           ubyte[16 * 1024] x;
00402049   push        edi
0040204A   lea         edi,[x]
00402050   rep stos    byte ptr [edi]
19:   }
00402052   pop         edi
00402053   mov         esp,ebp
00402055   pop         ebp
00402056   ret


August 11, 2004
van eeshan wrote:
> Thanks for clarifying that Walter. Would it be prudent to note that D
> allocates auto Objects on the heap? Stack allocation may be allowed for in
> the spec, but that's not how the compiler operates.
> 
> Also, there is that point about heap allocations being a lot more expensive
> than stack allocations. Naturally, one would lean towards wholeheartedly
> agreeing; but this is just not true when it comes to D. Here's a little
> (contrived) test jig to illustrate:

You'll notice, though, that there's absolutely nothing preventing D from performing these allocations on the stack as an optimization.

All the compiler needs is to be certain that the object's lifetime is limited to the scope.  Auto references offer precisely this.

(incidently, it is legal to write "auto int[] x = new int[...];")

 -- andy
August 11, 2004
Yep; agreed (and noted below). It just doesn't do that today, so I thought
it was worth a clarification (for those who didn't know).

"Andy Friesen" <andy@ikagames.com> wrote in message news:cfbpc5$13eh$1@digitaldaemon.com...
> van eeshan wrote:
> > Thanks for clarifying that Walter. Would it be prudent to note that D allocates auto Objects on the heap? Stack allocation may be allowed for
in
> > the spec, but that's not how the compiler operates.
> >
> > Also, there is that point about heap allocations being a lot more
expensive
> > than stack allocations. Naturally, one would lean towards wholeheartedly agreeing; but this is just not true when it comes to D. Here's a little (contrived) test jig to illustrate:
>
> You'll notice, though, that there's absolutely nothing preventing D from performing these allocations on the stack as an optimization.
>
> All the compiler needs is to be certain that the object's lifetime is limited to the scope.  Auto references offer precisely this.
>
> (incidently, it is legal to write "auto int[] x = new int[...];")
>
>   -- andy


August 11, 2004
Attached a little graph that shows arrays allocated on the heap versus arrays declared as local (stack) variables. You can see that stack allocations are faster only for array sizes of below ~64 bytes (on this machine), and quickly become significantly slower once you start using local arrays for anything bigger than around 512-bytes.

There's an interesting quirk at the 4096-byte mark: the codegen changes strategy slightly at this point, and I'd guess it is doing something akin to paging (ensuring the stack page-set is available), though can't be sure. Take a look at the previously posted assembler for reference.

If local (stack) arrays were to use the C/C++ approach, the time consumed would be ~10ms across the board, rather than the ~500ms for heap allocations. That is, for a 32KB local array, the initialization cost is ~865 times /more/ than it would be for the equivalent C/C++ approach (~10ms versus ~8650ms); almost three orders of magnatude.

This indicates two things:

1) making claims about D's perfomance superiority over Java due to the former's ability to use the stack (versus always on the heap) is based on speculation; not fact. Testing shows this to be entirely the opposite for arrays beyond 64 bytes in length. Similarly, any kind of performance testing against C/C++ within this realm will be viewed as a negative mark against D.

2) Implicit initialization is great. However, it can clearly and easily be demonstrated to be a serious impediment. Given that D is supposed to be a 'systems' language, I humbly suggest that a mechanism be provided to bypass such nicities when one is prepared to assume full responsibility. For example, there might be a qualifier for variables that disables the automatic initialization (along the lines of the 'auto' qualifier).

What do you folks think?









begin 666 stack allocation.PNG
MB5!.1PT*&@H````-24A$4@```C$```$L" (```"]K75[````!&=!34$`````
MBR5@30```"!C2%)-``````````````````````````````````````````"@
MYK6G```>2TE$051XG&+X/PI&P2@8!:-@% P.`!! # /M@%$P"D;!*!@%HP`*
M``)HM$X:!:-@%(R"43!8`$ `0>LDAE$P"D;!*!@%HV#@`*0R`@@@1)TT,'7B
M*!@%HV 4C((1#^!U$$ `C=9)HV 4C()1, H&&,#K(( `&JV31L$H& 6C8!0,
M,(#700`!-%HGC8)1, I&P2@88 "O@P`":+1.&@6C8!2,@E$PP !>!P$$T&B=
M- I&P2@8!:-@@ &\#@((H-$Z:12,@E$P"D;!``-X'0000*-UTB@8!:-@%(R"
M`0;P.@@@@$;KI%$P"D;!*!@%`PS@=1! `(W62:-@%(R"43 *!AC ZR" `*)5
MG81F(/+1$:1R1\$H& 6C8!0,;P`O\P$"B"9U$F8=@\P@B3L*1L$H& 6C8-@#
M>($/$$#TZ">-UDFC8!2,@E$P"O `>($/$$ #,'8W6B>-@E$P"D;!*$ &\ (?
M(("&6#\)?JIYPR@8!:-@%(P"O("ZI3I-`;S !PB@(58GT<BUHV 4C()1,,S
M$*V3``)H8,;NB.<28_@H& 6C8!2,`C0P1.LD@ `:DI,W0\NUHV 4C()10'\P
M1.LD@ `:K9-&P2@8!:-@&((A6B<!!-!HG30*1L$H& 7#$ S1.@D@@$;KI%$P
M"D;!*!B&8(C620`!-%HGC8)1, I&P3 $0[1.`@B@T3II%(R"43 *AB$8HG42
M0 "-UDFC8!2,@E$P#,$0K9,``FBT3AH%HV 4C()A"(9HG0000*-UTB@8!:-@
M% Q#,$3K)( `&JV31L$H& 6C8!B"(5HG`030:)TT"D;!*!@%PQ ,T3H)((!&
MZZ11, I&P2@8U("!@9S:98C620`!-%HGC8)1, I&P: &(ZI.`@B@T3II%(R"
M43 *!B\@KT+Z/V3K)( `&JV31L$H& 6C8) "LBND_T.V3@((H-$Z:12,@E$P
M"@8I&(%U$D `C=9)HV 4C()1,!@!)172_R%;)P$$T&B=- I&P2@8!8,1C,PZ
M"2" 1NND43 *1L$H&'2 P@KI_Y"MDP`"B%9U$IJ!#&! 'I>@X:-@%(R"43"<
M`.45TO\A6R<!!!!-ZB3,.@:901(7E_E4=.TH& 6C8!0,*C"2ZR2 `*)'/XD!
M!M#M'JV31L$H& 6C`!50I4+Z/V3K)( `HE.=A,P8K9-&P2@8!:,`*Z!6A?1_
MR-9)``$TQ.HDM"[7*!@%HV 4#"<P6B<!!- 0JY-HY-I1, I&P2@8<$#%"NG_
MD*V3``)H`-;=84XOX>$28_@H& 6C8!0,=4#="NG_D*V3``)H='_2*!@%HV 4
M##P8K9,@#( `&JV31L$H& 6C8( !U2ND_T.V3@((H-$Z:12,@E$P"@82T*)"
M^C]DZR2 `!JMDT;!*!@%HV @P6B=]!^I5 <(H-$Z:12,@E$P"@8,T*A"^C]D
MZR2 `!JMDT;!*!@%HV# P&B=! 'P4AT@@$;KI%$P"D;!*!@80+L*Z?^0K9,`
M`FBT3AH%HV 4C((!`#2MD/X/V3H)((!&ZZ11, I&P2@8`#!:)R$#>*D.$$"C
M==(H& 6C8!30&]"Z0OH_9.LD@ `:K9-&P2@8!:. KH .%=+_(5LG`030:)TT
M"D;!*!@%= 6C=1(F@)?J``$T6B>-@E$P"D8!_0!]*J3_0[9.`@B@T3II%(R"
M43 *Z 3H5B']'[)U$D `C=9)HV 4C()10"<P6B?A`O!2'2" 1NND43 *1L$H
MH >@9X7T?\C620`!-%HGC8)1, I&`<T!G2ND_T.V3@((H-$Z:12,@E$P"F@.
M1NLD_ !>J@,$T&B=- I&P2@8!;0%]*^0_@_9.@D@@&A5)V$U$&$K&""+X^$2
M:?@H& 6C8!0,3C!:)Q$$\%(=((!H4B=AK53@@L@U$T$N+O.IZ-I1, I&P2B@
M'1B0"NG_D*V3``*(3OTDY/IFM$X:!:-@%(P0,% 5TO\A6R<!!! ]ZB22*J'1
M.FD4C()1,&S :)U$)("7Z@`!1*<Z"0T@JR&I3D(S812,@E$P"@8M&, *Z?^0
MK9,``F@`UCB,]I-&P2@8!<,>#&R%]'_(UDD``30P=1):;PD/EWC#1\$H& 6C
M8/" T3J)) `OU0$":'1_TB@8!:-@%% 9#'B%]'_(UDD``31:)XV"43 *1@$U
MP6"HD/X/V3H)((!&ZZ11, I&P2B@)ABMD\@`\%(=((!&ZZ11, I&P2B@&A@D
M%=+_(5LG`030:)TT"D;!*!@%U &#IT+Z/V3K)( `&JV31L$H& 6C@#I@M$XB
M&\!+=8 `&JV31L$H& 6C@ I@4%5(_X=LG0000*-UTB@8!:-@%% !C-9)E !X
MJ0X00*-UTB@8!:-@%% *!EN%]'_(UDD``31:)XV"43 *1@%%8!!62/^';)T$
M$$"C==(H& 6C8!10!$;K),H!O%0'"*#1.FD4C()1, K(!X.S0OH_9.LD@ `:
MK9-&P2@8!:. 3#!H*Z3_0[9.`@B@T3II%(R"43 *R 2C=1*U`+Q4!PB@T3II
M%(R"43 *R &#N4+Z/V3K)( `&JV31L$H& 6C@!PP6B=1$<!+=8 `&JV31L$H
M& 6C@&0PR"ND_T.V3@((H-$Z:12,@E$P"D@#@[]"^C]DZR2 `!JMDT;!*!@%
MHX T,%HG41W 2W6 `*)5G81F( ,8D,<E:/@H& 6C8!30#0R)"NG_D*V3``*(
M)G429AV#S"")B\M\*KIV%(R"43 *B 1#I4+Z/V3K)( `HE,_"5EPM$X:!:-@
M% Q1,%HGT0C 2W6 `*)?G819V8S62:-@%(R"(02&4(7T?\C620`!-,3J) 88
MH*YK1\$H& 6C@" 8K9-H!^"E.D `T6^-`Q:[1_M)HV 4C((A`H96A?1_R-9)
M``%$CSJ)`0G\Q^CKX.<2-'P4C()1, IH#89<A?1_R-9)``$TNC]I%(R"43 *
M"(#1.HG6`%ZJ`P30:)TT"D;!*!@%^,!0K)#^#]DZ"2" 1NND43 *1L$HP F&
M:(7T?\C620`!-%HGC8)1, I&`4XP6B?1!\!+=8 `&JV31L$H& 6C`#L8NA72
M_R%;)P$$T&B=- I&P2@8!=C!:)U$-P`OU0$":+1.&@6C8!2,`BQ@2%=(_X=L
MG0000*-UTB@8!:-@%*"#H5XA_1^R=1) `(W62:-@%(R"48 .1NLD.@-XJ0X0
M0*-UTB@8!:-@%*" 85 A_1^R=1) `(W62:-@%(R"48 "1NLD^@-XJ0X00*-U
MTB@8!:-@%"# \*B0_@_9.@D@@$;KI%$P"D;!*(""85,A_1^R=1) `(W62:-@
M%(R"40`%HW720 %XJ0X00*-UTB@8!:-@%(# <*J0_@_9.@D@@$BKDQBP`5JY
M$:\SZ&_I*!@%HV 8@V%6(?T?LG420 "14"?A4D/_&F*T3AH%HV 44!>,UDD#
M"^"E.D `C8[=C8)1, I&.AA^%=+_(5LG`030:)TT"D;!*!CI8+1.&G `+]4!
M`HA6=1*:@6@S3R1Q"1H^"D;!*!@%9(-A62']'[)U$D `D5PG(73BUH)9QR S
M2.+B=\,H& 6C8!10`H9KA?1_R-9)``%$9IV$5G_@L>#_:)TT"D;!*!BL8 36
M25B73P\@@+L*P@`(H-$Z:12,@E$P0L$PKI#^XZV3Z.P2/ "SP <(('+FDTBM
M-JA8)Z%5K:-@%(R"44 V&*V3!AQ@%O@``42/-0ZC_:11, I&P6 #P[M"^C]D
MZR2 `"*SGT2POX)6)Z&-&Q+/)6CX*!@%HV 4D J&?87T?_#52;B&OM 8``%$
M_KJ[`02#P0VC8!2,@J$+1NLDJ@."QA)9)P$$T&B=- I&P2@866 D5$C_:5\G
M(8]I,6 #R,K^8ZM^L H"!!"MQNYH"D;KI%$P"D8!>6"$5$C_:5PG81J")H)9
M#Z&)H.F",P`":+2?- I&P2@806"T3D+MIC20BI#-P=7CP5H#8>W)8-9)``$T
M6B>-@E$P"D8*&#D5TG]ZS2>A52IXN$3VDP`"B)PZ:73L;A2,@E$P%,%HG?2?
M>F-WF/TDK+4#9FV$JW<%80`$$*WV)]$4#"W7CH)1, H&`QA1%=+_P;<6'"O
MK),``HB$.@F7&OK[<%"%Z2@8!:-@\(.15B']'[)U$D `D=9/PNR=#8CW!E68
MCH)1, H&/QBMD^!@4)6?F'420 "-CMV-@E$P"H8Y&($5TO\A6R<!!-!HG30*
M1L$H&,Y@9%9(_X=LG0000*-UTB@8!:-@.(/1.@D-#*KR$[-.`@@@\L]Q(%47
M%<&@"M-1, I&P: %([9"^C]DZR2 `")SS^QHG30*1L$H&/Q@M$["!(.J_,2L
MDP`":+1.&@6C8!0,3S"2*Z3_=#_OCD)SX R `")_[&X`*X;1.FD4C()10!",
MUDE8Q0=YG0000*-K'$;!*!@%PQ",\ KI/]W/%H(+HBF #ZIA[<E@UDD``411
M/VET[&X4C()1,#C!:)U$5)W$0#I"-00/`YF+7Q:9`1! 9,XG#2P8#&X8!:-@
M% Q:,%HA_:?7V!VNCA&R"%;UN,P!"" ZU4EHG2J2N-1RPR@8!:-@A(#1.NG_
M0-1)>!007R<!!! ]QN[P.XY(IV,U<!2,@E$P"M# :(4$`72ND_YC=(S(FT\"
M""!Z])-&ZZ11, I&`=W :)T$`8-J?Q(N2S$+?( `&H"QN]$Z:12,@E% (S!:
M(<'!$*V3``*(G#II`,?N2+)W%(R"43#2P&B=! >#JD["!3 +?( `(F<^B4);
M1_M)HV 4C ):@-$*"1G@J9,&%8"["L(`"" 2ZB0&C)DK8G0AAP):B!##Q>.2
M43 *1L$H0 :C=1(RP%4G#4X`+]4!`H@>_22J@Z'EVE$P"D8!'<!HA80&AFB=
M!!! %*UQ&*BZ8;1.&@6C8!2@@=$Z"0T,T3H)((!(&[O#-11(9S!:)XV"43 *
MD,%HA80)AFB=!!! =%H+3ETP&-PP"D;!*!@\8+1.P@1#M$X""*#1^:11, I&
MP= &HQ425C!$ZR2 `!JMDT;!*!@%0QN,UDE8P1"MDP`":+1.&@6C8!0,83!:
M(>$"0[1.`@B@T3II%(R"43"$P6B=A L,T3H)((!&ZZ11, I&P5 %HQ42'C!$
MZR2 `!JMDT;!*!@%0Q6,UDEXP!"MDP`":+1.&@6C8!0,23!:(>$'0[1.`@B@
MT3II%(R"43 DP6B=A!\,T3H)((!&ZZ11, I&P= #HQ4203!$ZR2 `!JMDT;!
M*!@%0P^,UDD$P1"MDP`":+1.&@6C8!0,,3!:(1$#AFB=!!! HW72*!@%HV"(
M@=$ZB1@P1.LD@ `:K9-&P2@8!4,)C%9(1((A6B<!!-!HG30*1L$H&$I@M$XB
M$@S1.@D@@.A4)Z%=MD02%ZMIM'#D*!@%HV"0@]$*B7@P1.LD@ "B1YV$L S,
M((F+W\!1, I&P8@"HW42\6"(UDD``42G.@FYZS-:)XV"43 *R "C%1))8(C6
M20`!--I/&@6C8!0,#3!:)Y$$AFB=!!! 0ZQ.0NMRC8)1, I&"!BMD$@%0[1.
M`@B@(58G$90:!:-@% Q+,%HGD0J&:)T$$$ #L.X.<WH)#Q>7:31U[2@8!:-@
ML('1.HE4,$3K)( `&MV?- I&P2@8[&"T0B(##-$Z"2" 1NND43 *1L%@!Z-U
M$AE@B-9)``$T6B>-@E% !3!::-(.C(8M>6"(UDD``31:)XV"44 I@!2:HT4G
MC<!HP)('AFB=!!! HW72*!@%% %XB3E:=-("C(8JV6"(UDD``31:)XV"44 ^
M0"LQ1PM0JH/1("4;#-$Z"2" 1NND43 *R 28Q>5H`4I=,!J>E( A6B<!!-!H
MG30*1@$Y`%=Q.5J,4A&,!B8E8(C620`!-%HGC8)10#+ 4U:.%J/4`J,A22$8
MHG420 "-UDFC8!20#/ 7EZ.%*57 :#!2"(9HG0000*-UTB@8!:0!@F7E:&%*
M.1@-0\K!$*V3``)HM$X:!:. !$!D63E:I%((1@.0<C!$ZR2 `!JMDT;!*" 6
MD%10CI:J9(/1H*,*&*)U$D `C=9)HV 4$ 5(+2A'"U:RP6C0404,T3H)((!&
MZZ11, H(`_)*R=&RE0PP&FC4`D.T3@((H-$Z:12,`@* [%)RM'@E`XP&&K7
M$*V3``)HM$X:!:,`'Z"PB!PM84D"H\%%13!$ZR2 `!JMDT;!*, )*"\B1PM9
MDL!H<%$1#-$Z"2" 1NND43 *L -JE8^CY2R18#2@J N&:)T$$$"C==(H& 58
M`!7+Q]&BED@P&E#4!4.T3@(((+K620A;P0!9' \7CSFC8!30`E"]<!PM;0F"
MT2"B.ABB=1) `-&O3H+7-,@U$T$N+J-HZM11,,(!+<K'T3(7/Q@-'ZJ#(5HG
M`000G>HDY/IFM$X:!8,9T*AP'"US\8#1P*$%&*)U$D `T:-.(JD2&JV31L$`
M`IH6CJ,E+RXP&C*T`$.T3@(((#K526@`V5*2ZB0T$T;!** BH'7).%KR8@6C
MP4(C,$3K)( `&H U#J/]I%$P" %]2L;1\A<3C(8)C< 0K9,``FA@ZB2TWA(>
M+AYS1L$HH!:@6[$X6OZB@=$`H1T8HG420 "-[D\:!2,=T+E8'"V%D<%H:- .
M#-$Z"2" 1NND43"B`?W+Q-%2& Y&@X*F8(C620`!-%HGC8*1"P:J3!PMBR%@
M-!QH"H9HG0000*-UTB@8H6!@"\31XG@T!&@-AFB=!!! HW72*!B)8, +Q %W
MP("#T1"@-1BB=1) `(W62:-@Q(%!4AH.$F?0'P`]/F+]3D\P1.LD@ `:K9-&
MP8@#@Z1 '"3.H"<8K8WH"89HG0000*-UTB@866!0E8F#RC&T!B/*LX,!#-$Z
M"2" 1NND43""P& K%@>;>V@$1KM'`P*&:)T$$$"C==(H&"E@<!:+@]-55 3#
MWH.#%@S1.@D@@$;KI%$P(L!@+AD'L]LH`:/=HX$%0[1.`@B@T3II% Q_,,A+
MQD'N/#+ :&TT&, 0K9,``FBT3AH%PQP,B<)Q2#B22#"<_#*DP1"MDP`":+1.
M&@7#%@RAUOI0<2=^,(0"?"2 (5HG`030:)TT"H8A&(J%XY!S,#(8B@$^[,$0
MK9,``FBT3AH%PPH,W<)QB#K[_U!V^? &0[1.`@B@T3II% P3,'1K(S@8<NX?
M!F$^C,$0K9,``FBT3AH%0QX,FY)Q:/EB:+EV!((A6B<!!-!HG30*AC 8-K41
M' P)[PR_8!^68(C620`!1*<ZB0$,R.-B-8T6CAP%0P@,XV)Q,/MK& ?[\ -#
MM$X"""!ZU$D(R\ ,DKCX#1P%(Q ,^V)QT/INT#IL%& %0[1.`@@@NH[=C=9)
MHX 2,.QK(S@8;-X<.2$_G, 0K9,``HA^=1)F93-:)XT"(L%(*Q,'E6<'E6-&
M`?%@B-9)``$TQ.HD!AB@M6M'P2 !(ZTV@H/!X.L1&_C#`PS1.@D@@.BWQ@&+
MW:/]I%& &XSP`G%@_3["`W]X@"%:)P$$$)W6."#W;]#Z.OBYN RDG6M'P8"#
MT0(1`@8D$$8#?]B (5HG`030Z/ZD43"(P&B!B SH&120D!\-_.$$AFB=!!!
MHW72*!@48+1 Q IH'2:C5=$P!D.T3@((H-$Z:10,,!@M$_$#6@3.:%4T$L 0
MK9,``FBT3AH%`P9&BT5B`!6#:+0J&E%@B-9)``$T6B>-`KH">+$X6C(2#R@)
MJ]$`'[%@B-9)``$T6B>-`GJ T6*1$D!&N(T&^"@8HG420 "-UDFC@(9@M&2D
M%B R#$<#?!3 P1"MDP`":+1.&@54!J.#1;0`^ -S-,!'`288HG420 "-UDFC
M@#I@M%BD-< ,V]$P'P5XP!"MDP`":+1.&@7D@]$N$3T!/)!'PWP4$ .&:)T$
M$$"C==(H(!F,EHD#!4:#?100#X9HG0000*-UTB@@%HQ61:-@% PA,$3K)( `
M&JV31@$^,#HZ-PI&P1 %0[1.`@B@T3II%" `<@TT6@^-@E$PI,$0K9,``FBT
M3AJ)`+/N&:V!1L$H&&9@B-9)``$T6B<-6X"KXAFM>T;!*!@)8(C620`!-%HG
M#7E M8J'812-HE$T6!'I8(C620`!Q(#&'Q)@:+F6;("GHT-RW4.;1#\*1L$H
M&+1@B-9)``$T&.LD!C# KX!NCJ$6(+*"(;.C,UK?C()1, I0P1"MDP`":-#5
M20B7X782.:X=\*[W(.O7CX)1, J&-QBB=1) `(V8.@F?C;3LP8R"43 *1L%
M@"%:)P$$T$BIDT8KF%$P"D;!B )#M$X""* A5B<QC()1, I&P2@@`@S1.@D@
M@(98G410BA8N&;5E\-@R;#PR:LL@M&+4E@$$<-<"!-!@K),@`+\:^KADU);!
M9LNP\<BH+8/0BE%;!A# 70L00(.N3B(&#*<8';5EL%DQ:LO@M&78>&28V4(M
M`'<M0 `-R3II%(R"43 *1L%P`O Z""" 1NND43 *1L$H& 4##.!U$$ `C=9)
MHV 4C()1, H&&,#K(( `&JV31L$H& 6C8!0,,(#700`!-%HGC8)1, I&P2@8
M8 "O@P`":+1.&@6C8!2,@E$PP !>!P$$X-Z,<0``01CH_U_M1@Q8H-K!R.AP
M;0G$B9__)'?G5)X]253L42N!Y"2A(L1=B0E5G/G<!LM'*$1FY3I85=,01S(`
MY=#>JU"TLR5*L&.IIH=FG*UYAV5G`#4DQI%D>;,LPA1 P[9.0HX_3"Z-;(&S
MJ6@+6EI$9E#%4[B\@%\!)1;!N52TA8Q0HJ14PF4LW$QJ>0>_I>390C#14FX+
M2::1EXF(CV7*?80G6G$E8^)M(9@!\1M+HY*-_@#N?H `W%4Q$@`@"/K_JVMK
M2$!3N^MR<PA25#ZI1X10MP4<#N4EYV,L+73;FK$T#6Y!(&::2-^X@18[;1B"
MKBZ-P+%I0AJW/Y$&'K' 3[KF%#<,EHJ1AF\%OI U7BG#MS<DLH"5&7@P5@E3
M``WS.HF23$62^9271,38@LFE5G+$E<<PN12:C]4B/"*46('++LHK#$P&5G'*
MS2>)2Y(M)%42Y%E!O&D45A@$N63'#C$!3F&XX7<D>98.10!W/T `#1/_X &4
MY"OB#4=KLU"WY4)\3J.6%<B"U$WT@Z1.(CN:\!0<6(TEK[; 8PZR.'FVX-*%
M-8BPRI)G"Y')F-38P1/+N.PB/MPP'4-,R) 4;G@<@R>"R/#+( =P]P,$T##Q
M#R8@F"5H9 LM["(RIU'%?$QCJ6(+5D.H&VAX8AR7R627LW@,IU:@836'*E%#
M:B5!JOGX#2'>%OR6DJ2=\G##HY'"<".HG19I8! "N/L!`G!;)2D`@"#P_[_N
M%J+FC$L0><O#;$KXB1^WY#FCCIU+++(Y2R&YK*\FN$TF?G:(5">6D<574! Y
M^Y5+'(C9#.W$,C(:F 89(-1/:JY-)Q894Y3MN.))28P11NW(#KQ6V\(20,.Y
M3AH%HV 4C()1,"0`O X""*#1.FD4C()1, I&P0`#>!T$$$"C==(H& 6C8!2,
M@@$&\#H(((!&ZZ11, I&P2@8!0,,X'400 "-UDFC8!2,@E$P"@88P.L@@ `:
MK9-&P2@8!:-@% PP@-=!``$T6B>-@E$P"D;!*!A@`*^#``)HM$X:!:-@%(R"
M43# `%X'`030:)TT"D;!*!@%HV" `;P.`@B@T3II%(R"43 *1L$``W@=!!!
MHW72*!@%*(",(V?P:"'>M-$\. I&,H"G?X `&JV31L$H(!/@.EH-JQJ2#!P%
MHV"D`7CB!PB@T3II%(P"E*-.X22:()Y#0C$58QJ+:0CF`9VCV7 4C%@`3_P`
M`31:)XV"D0[P'_/\'W=_"*LX9L6&53'6'#>:#4?!B 7PQ \00*-UTB@8!?@J
MC_\8W2!D76B,_WCK)/S=IO^CV7 4C& `3_P``31:)XV"40`%:-4)FC@N]5@5
MX^DGX3($CYI1, J&/8 G?H `&JV31L%(!YC=E_\8W1J"_21<DT-8NTH$#1P%
MHV"D`7CB!PB@T3II%(P",@'^7$-&GAK-AJ-@Q )XX@<(H-$Z:12,`O(!KJ4*
MHQ72*!@%) %X^@<(H-$Z:12,@E$P"D;!``-X'0000*-UTB@8!:-@%(R"`0;P
M.@@@@$;KI%$P"D;!*!@%`PS@=1! `(W62:-@%(R"43 *!AC ZR" `!JMDT;!
M*!@%HV 4##" UT$``31:)XV"43 *1L$H&& `KX,``FBT3AH%HV 4C()1,, `
M7@<!!-!HG30*1L$H& 6C8( !O X""*#1.FD4C()1, I&P0`#>!T$$$"C==(H
M& 6C8!2,@@$&\#H((("P'"(Y"D;!*!@%HV 4T!E *B. `!KM'HV"43 *1L$H
J&"P`((!&ZZ11, I&P2@8!8,%``08`&FN<"M[6$Y2`````$E%3D2N0F""
`
end

August 11, 2004
In article <cfdoer$13pt$1@digitaldaemon.com>, van eeshan says...
>
>1) making claims about D's perfomance superiority over Java due to the former's ability to use the stack (versus always on the heap) is based on speculation; not fact. Testing shows this to be entirely the opposite for arrays beyond 64 bytes in length. Similarly, any kind of performance testing against C/C++ within this realm will be viewed as a negative mark against D.

Regan, if I remember correctly, reported a bug where executable size is proportional to the size of static arrays the application contains.  This performance issue sounds like it may be related.

>2) Implicit initialization is great. However, it can clearly and easily be demonstrated to be a serious impediment. Given that D is supposed to be a 'systems' language, I humbly suggest that a mechanism be provided to bypass such nicities when one is prepared to assume full responsibility. For example, there might be a qualifier for variables that disables the automatic initialization (along the lines of the 'auto' qualifier).

An impediment how?  Just in terms of performance?  In general, I would say that default initialization is worth the performance cost for its ability to prevent bugs.


Sean


August 11, 2004
>>2) Implicit initialization is great. However, it can clearly and easily be
>>demonstrated to be a serious impediment. Given that D is supposed to be a
>>'systems' language, I humbly suggest that a mechanism be provided to bypass
>>such nicities when one is prepared to assume full responsibility. For
>>example, there might be a qualifier for variables that disables the
>>automatic initialization (along the lines of the 'auto' qualifier).
> 
> 
> An impediment how?  Just in terms of performance?  In general, I would say that
> default initialization is worth the performance cost for its ability to prevent
> bugs.
> 

That's why I think the ability to have it on by default is great.  If it were able to be turned off, that is no different from me reusing a buffer.  The buffer is only initialized once, yet I re-use it thousands of times without much problem.

Performance does and will always matter, regardless of the secret contract between Intel and Microsoft to castrate newer, faster PCs. MHO, of course.

Scott
August 11, 2004
"Sean Kelly s" <sean@f4.ca> wrote in message news:cfe4hu$19cf$1@digitaldaemon.com...
> In article <cfdoer$13pt$1@digitaldaemon.com>, van eeshan says...
> >
> >1) making claims about D's perfomance superiority over Java due to the former's ability to use the stack (versus always on the heap) is based on speculation; not fact. Testing shows this to be entirely the opposite for arrays beyond 64 bytes in length. Similarly, any kind of performance
testing
> >against C/C++ within this realm will be viewed as a negative mark against
D.
>
> Regan, if I remember correctly, reported a bug where executable size is proportional to the size of static arrays the application contains.  This performance issue sounds like it may be related.

AFAIK this is not related in the slightest, I'm afraid. This topic is purely about CPU cycles, and the stack. Nothing to do with static data or executable size.

> >2) Implicit initialization is great. However, it can clearly and easily
be
> >demonstrated to be a serious impediment. Given that D is supposed to be a 'systems' language, I humbly suggest that a mechanism be provided to
bypass
> >such nicities when one is prepared to assume full responsibility. For example, there might be a qualifier for variables that disables the automatic initialization (along the lines of the 'auto' qualifier).
>
> An impediment how?  Just in terms of performance?  In general, I would say
that
> default initialization is worth the performance cost for its ability to
prevent
> bugs.

I don't think anything negative was said about default initialization as a feature, Sean. If it was then I apologize. Default/implicit initialization is great (as was noted; so we agree), but there are times when you need to take full control over what's going on. It may not matter to you specifically, but there are many situations whereby one needs to take full responsibility over a select set of variables (such as temporary stack-based buffers). Providing the mechanism as an /option/ is not detrimental to the language. It's like applying "const", or one of the other optional qualifiers.

I'm just illustrating that the language could really use a means to disable default-initialization for those cases where it is deemed both completely unecessary and too costly. Surely that's not too much to consider?


August 11, 2004
Have you tried alloca? I haven't tried running it but I'm thinking of

void stack2()
{
  void* x = alloca(16*1024);
}


van eeshan wrote:

> "Walter" <newshound@digitalmars.com> wrote in message news:cfbip7$ora$1@digitaldaemon.com...
>>
>> "van eeshan" <vanee@hotmail.net> wrote in message news:cfb72j$9l7$1@digitaldaemon.com...
>> > "Walter" <newshound@digitalmars.com> wrote in message news:cfb5v9$76u$1@digitaldaemon.com...
>> > > The problem, however, is that since Java does not allow any objects or arrays on the stack (or in static data), whenever you need one it
> needs
>> to
>> > > be allocated on the heap. This is a lot more expensive than stack allocation. Since one winds up allocating a lot more heap objects in
>> Java
>> > > than one does in C/C++, the end result is slower. Java offers no alternatives to gc allocation.
>> > >
>> > > This is why D allows stack based objects and value objects.
>> >
>> > Are you saying that D allows one to create Objects entirely upon the
>> stack?
>>
>> For auto objects, it is allowed for the compiler to put them there. But I was primarilly referring to structs and arrays.
>>
>> > And entirely within static data?
>>
>> Structs and arrays, yes. Java does not allow structs, nor does it allow arrays on the stack.
> 
> 
> Thanks for clarifying that Walter. Would it be prudent to note that D allocates auto Objects on the heap? Stack allocation may be allowed for in the spec, but that's not how the compiler operates.
> 
> Also, there is that point about heap allocations being a lot more expensive than stack allocations. Naturally, one would lean towards wholeheartedly agreeing; but this is just not true when it comes to D. Here's a little (contrived) test jig to illustrate:
> 
> private import std.c.time;
> private import std.c.stdlib;
> private import std.c.windows.windows;
> 
> void heap()
> {
>         void *x = malloc (16 * 1024);
>         free (x);
> }
> 
> void stack()
> {
>         ubyte[16 * 1024] x;
> }
> 
> void trace (uint startTime)
> {
>         FILETIME ft;
>         GetSystemTimeAsFileTime(&ft);
>         printf ("%u\n", (ft.dwLowDateTime - startTime) / 10000);
> }
> 
> void main()
> {
>         FILETIME start;
> 
>        GetSystemTimeAsFileTime(&start);
>         trace (start.dwLowDateTime);
> 
>         sleep (3);
>         trace (start.dwLowDateTime);
> 
>         for (int i=1_000_000; --i;)
>              heap();
> 
>         trace (start.dwLowDateTime);
> 
>         for (int i=1_000_000; --i;)
>              stack();
> 
>         trace (start.dwLowDateTime);
> }
> 
> The results? On this machine it takes the heap() routine ~500ms to execute, and the stack() version ~3500ms. Yep, that's seven times longer. Why? What wasn't stated is that D ensures all stack variables are initialized ... including arrays. The innocuous stack allocation actually clears the 16KB to zero each time, which is why it takes so long. For a 32KB 'buffer', the stack() execution time goes up to ~8600ms versus the ~500ms for heap(); you can see there's some rather non-linear behavior for the stack version <g>
> 
> The point here is not about the benefits/detriments of deterministic initialization. It's about clarifying a point of performance-tuning that is far from obvious. Without wishing to put too fine a point on it, the quoted post was somewhat misleading. That is; allocating an array on the D stack can consume far more cycles than the equivalent heap allocation. It depends upon the size of the array, the bus speed, the size of the cache, heap fragmentation and many other things.
> 
> D stack allocations are simply not like C/C++ at all. Far from it.
> 
> 
> For the curious, here's the disassembly for both routines. It's worth noting that the array initialization could be sped up. Also worth noting is that the loop/call overhead was 10ms.
> 
> 10:   {
> 11:           void *x = malloc (16 * 1024);
> 12:           free (x);
> 00402011   push        4000h
> 00402016   call        _malloc (0040574c)
> 0040201B   add         esp,4
> 0040201E   push        eax
> 0040201F   call        _free (004057a4)
> 00402024   add         esp,4
> 13:   }
> 00402027   pop         eax
> 00402028   ret
> 14:
> 15:
> 16:   void stack()
> 0040202C   push        ebp
> 0040202D   mov         ebp,esp
> 0040202F   mov         edx,4
> 00402034   sub         esp,1000h
> 0040203A   test        dword ptr [esp],esp
> 0040203D   dec         edx
> 0040203E   jne         _D5hello5stackFZv+8 (00402034)
> 00402040   sub         esp,edx
> 00402042   mov         ecx,4000h
> 00402047   xor         eax,eax
> 17:   {
> 18:           ubyte[16 * 1024] x;
> 00402049   push        edi
> 0040204A   lea         edi,[x]
> 00402050   rep stos    byte ptr [edi]
> 19:   }
> 00402052   pop         edi
> 00402053   mov         esp,ebp
> 00402055   pop         ebp
> 00402056   ret

August 11, 2004
"Ben Hinkle" <bhinkle4@juno.com> wrote in message news:cfe87l$1akg$1@digitaldaemon.com...
> Have you tried alloca? I haven't tried running it but I'm thinking of
>
> void stack2()
> {
>   void* x = alloca(16*1024);
> }

Tried that, Ben; alloca() also clears everything to zero.


August 11, 2004
In article <cfe60s$1a2i$1@digitaldaemon.com>, van eeshan says...
>
>"Sean Kelly s" <sean@f4.ca> wrote in message news:cfe4hu$19cf$1@digitaldaemon.com...
>
>> Regan, if I remember correctly, reported a bug where executable size is proportional to the size of static arrays the application contains.  This performance issue sounds like it may be related.
>
>AFAIK this is not related in the slightest, I'm afraid. This topic is purely about CPU cycles, and the stack. Nothing to do with static data or executable size.

Ah okay.  I thought perhaps the current code generation involving arrays had issues that might be corrected in the future.

>> An impediment how?  Just in terms of performance?  In general, I would say
>that
>> default initialization is worth the performance cost for its ability to
>prevent
>> bugs.
>
>I don't think anything negative was said about default initialization as a feature, Sean. If it was then I apologize. Default/implicit initialization is great (as was noted; so we agree), but there are times when you need to take full control over what's going on. It may not matter to you specifically, but there are many situations whereby one needs to take full responsibility over a select set of variables (such as temporary stack-based buffers). Providing the mechanism as an /option/ is not detrimental to the language. It's like applying "const", or one of the other optional qualifiers.
>
>I'm just illustrating that the language could really use a means to disable default-initialization for those cases where it is deemed both completely unecessary and too costly. Surely that's not too much to consider?

Not at all.  However this might violate Walter's rule against pragmas.  Even so, I had overlooked the fact that declaring an array would implicitly initialize all array elements.  This kind of stinks from a performance perspective, since 90% of the time I use arrays I have no need for them to be initialized.  Perhaps a new attribute?

declare int x[10000000];
declare {
float a[100000];
char b[1000000];
}


Sean


« First   ‹ Prev
1 2 3 4 5 6