Prev: passing a type of different KIND to a C function from Fortran ?binding
Next: ALLOCATABLE array as MPI buffer
From: Arjen Markus on 28 May 2010 08:36 On 28 mei, 14:24, m_b_metcalf <michaelmetc...(a)compuserve.com> wrote: > On May 28, 1:24 pm, Hifi-Comp <wenbinyu.hea...(a)gmail.com> wrote: > > > In fact I have already had all the operations overloaded including all > > intrinsic functions, math operations (+-*/ **) and relational > > operators. One thing I am not satisfied is the speed. With /, the time > > for analysis remains the same, yet for the overloaded code it runs for > > 6.25 secs (CVF 6.6) and 7.25 secs (gfortran 4.3), For those who are > > interested to test the speed, I am pasting the source codes here: > > > PROGRAM Test > > USE DNAD > > USE CPUTime > > > IMPLICIT NONE > > REAL(8):: x_,y_,z_,f_,ftot_ > > TYPE(DUAL_NUM):: x,y,z,f,ftot > > INTEGER:: I > > > x_=1.0d0;y_=2.0d0;z_=0.3d0 > > ftot_=0.0d0 > > > CALL TIC > > > DO i=1,50000000 > > f_=x_-y_*z_/x_ > > ftot_ = ftot_ - f_ > > ENDDO > > WRITE(*,*)'Analysis Runs for ', TOC(),' Seconds.' > > > write(*,*)ftot_ > > > x=DUAL_NUM(1.0d0,0.1D0);y=DUAL_NUM(2.0d0,0.2D0);z=DUAL_NUM(0.3d0,0.3D0) > > ftot=DUAL_NUM(0.0d0,0.0D0) > > > CALL TIC > > > DO i=1,50000000 > > f=X-y*z/x > > ftot = ftot - f > > ENDDO > > WRITE(*,*)'DNAD Runs for ', TOC(),' Seconds.' > > > write(*,*)ftot_ > > > END PROGRAM Test > > > MODULE CPUTime > > IMPLICIT NONE > > PRIVATE > > PUBLIC TIC, TOC > > INTEGER::start, rate, finish > > CONTAINS > > > SUBROUTINE TIC > > CALL SYSTEM_CLOCK(start,rate) > > END SUBROUTINE TIC > > > FUNCTION TOC() RESULT(sec) > > > REAL::sec > > > CALL SYSTEM_CLOCK(finish) > > IF(finish>start) THEN > > sec=REAL(finish-start)/REAL(rate) > > ELSE > > sec=0.0 > > ENDIF > > > END FUNCTION TOC > > END MODULE CPUTime > > > MODULE DNAD > > IMPLICIT NONE > > PRIVATE > > INTEGER, PARAMETER:: DBL_AD=SELECTED_REAL_KIND(15) > > REAL(DBL_AD) ::negative_one=-1.0d0 > > > TYPE,PUBLIC:: DUAL_NUM > > REAL(DBL_AD)::x_ad_ > > REAL(DBL_AD)::xp_ad_ > > END TYPE DUAL_NUM > > > PUBLIC OPERATOR (-) > > INTERFACE OPERATOR (-) > > MODULE PROCEDURE MINUS_DD > > END INTERFACE > > > PUBLIC OPERATOR (*) > > INTERFACE OPERATOR (*) > > MODULE PROCEDURE MULT_DD > > END INTERFACE > > > PUBLIC OPERATOR (/) > > INTERFACE OPERATOR (/) > > MODULE PROCEDURE DIV_DD > > END INTERFACE > > > CONTAINS > > > ELEMENTAL FUNCTION MINUS_DD(u,v) RESULT(res) > > TYPE (DUAL_NUM), INTENT(IN)::u,v > > TYPE (DUAL_NUM)::res > > > res%x_ad_ = u%x_ad_-v%x_ad_ > > res%xp_ad_= u%xp_ad_-v%xp_ad_ > > > END FUNCTION MINUS_DD > > > ELEMENTAL FUNCTION MULT_DD(u,v) RESULT(res) > > TYPE (DUAL_NUM), INTENT(IN)::u,v > > TYPE (DUAL_NUM)::res > > > res%x_ad_ = u%x_ad_*v%x_ad_ > > res%xp_ad_= u%xp_ad_*v%x_ad_ + u%x_ad_*v%xp_ad_ > > > END FUNCTION MULT_DD > > > ELEMENTAL FUNCTION DIV_DD(u,v) RESULT(res) > > TYPE (DUAL_NUM), INTENT(IN)::u,v > > REAL(DBL_AD)::tmp > > TYPE (DUAL_NUM)::res > > INTEGER:: i > > > tmp=1.D0/v%x_ad_ > > res%x_ad_ = u%x_ad_*tmp > > res%xp_ad_ =(u%xp_ad_- res%x_ad_*v%xp_ad_)*tmp > > > END FUNCTION DIV_DD > > > END MODULE DNAD > > This is what I get with Intel's compiler on a 2GHz PC. Msybe you need > to upgrade? > > Analysis Runs for 0.1050000 Seconds. > -19999999.9990236 > DNAD Runs for 0.1040000 Seconds. > -19999999.9990236 > Press any key to continue . . . > > Regards, > > Mike Metcalf I get very similar results with Intel 11.1 on a laptop, but for gfortran version 4.4.3 on the same machine, the times are: 0.219 and 2.844 seconds. Regards, Arjen
From: Hifi-Comp on 28 May 2010 08:36 On May 28, 8:32 am, m_b_metcalf <michaelmetc...(a)compuserve.com> wrote: > On May 28, 2:24 pm, m_b_metcalf <michaelmetc...(a)compuserve.com> wrote: > > > > This is what I get with Intel's compiler on a 2GHz PC. Msybe you need > > to upgrade? > > > Analysis Runs for 0.1050000 Seconds. > > -19999999.9990236 > > DNAD Runs for 0.1040000 Seconds. > > -19999999.9990236 > > Press any key to continue . . . > > > Regards, > > > Mike Metcalf- Hide quoted text - > > > - Show quoted text - > > Correcting the code (superfluous _ on ftot) gives: > Analysis Runs for 0.1060000 Seconds. > -19999999.9990236 > DNAD Runs for 0.1050000 Seconds. > -19999999.9990236 25000000.0000000 > Press any key to continue . . .- Hide quoted text - > > - Show quoted text - Amazing, how it possible DNAD run is more efficient than the Analysis run? As DNAD run definitely perform more calculations (- twice, * three times, / three more multiplications) than Analysis run.
From: Aris on 28 May 2010 08:36 Kay Diederichs <kay.diederichs(a)uni-konstanz.de> wrote: > mecej4 schrieb: >> >> You have no provision for carries and overflows in your multiplication. And, >> you have not yet reached the fun part: division. Once you implement >> division, you will appreciate why doing multiple-precision floating point >> arithmetic in software is undertaken only if unavoidable. >> >> -- mecej4 > > I understand your comment as meaning that you have identified the code > as doing a part of interval arithmetics (at least that's what I think > it's headed to), and that furthermore you have looked into that more deeply. > I am quite interested in learning about existing software (e.g. Fortran > MODULE) that allows to (as simply as possible) convert an existing > program from normal arithmetics to interval arithmetics, e.g. to > pinpoint parts of code that benefit from higher precision calculations. > > Another "fun part" of that, once one has the + - * / is, I guess, to > provide overloaded functions of min max abs sqrt exp log sin cos tan and > so on. But it would be extremely useful, I'd say. The * / and the functions seem to be the easy part. sqrt(x+eps) -> sqrt(x)+eps/sqrt(x)/2 exp(x+eps) -> exp(x)+eps*exp(x) etc. To my understanding, + and - are the difficult ones. In fact, the addition function given by Hifi-Comp only makes sense if u and v are living at exactly the same scale.
From: Tobias Burnus on 28 May 2010 08:47 On 05/28/2010 02:24 PM, m_b_metcalf wrote: >> DO i=1,50000000 >> f=X-y*z/x >> ftot = ftot - f >> ENDDO >> WRITE(*,*)'DNAD Runs for ', TOC(),' Seconds.' >> write(*,*)ftot_ I think you want to print here ftot_ - otherwise, calculating the second loop takes 0.0000 seconds ;-) > This is what I get with Intel's compiler on a 2GHz PC. Msybe you need > to upgrade? > > Analysis Runs for 0.1050000 Seconds. > -19999999.9990236 > DNAD Runs for 0.1040000 Seconds. > -19999999.9990236 Using: $ gfortran -Ofast -march=native -flto -fwhole-program test.f90 I get on my dated AMD64: $ ./a.out Analysis Runs for 0.11900000 Seconds. -19999999.999023605 DNAD Runs for 8.29999968E-02 Seconds. -19999999.999023605 24999999.999999996 (Actually, the crucial option is -O1 and -fwhole-file, which exists since 4.5 and presumably will become default in 4.6. That option is enabled implicitly via -flto. The additional -fwhole-program only reduces the file size by a small amount, -march=native can never harm and -Ofast is identically to -O3 -ffast-math.) Tobias
From: Hifi-Comp on 28 May 2010 09:04
On May 28, 8:47 am, Tobias Burnus <bur...(a)net-b.de> wrote: > On 05/28/2010 02:24 PM, m_b_metcalf wrote: > > >> DO i=1,50000000 > >> f=X-y*z/x > >> ftot = ftot - f > >> ENDDO > >> WRITE(*,*)'DNAD Runs for ', TOC(),' Seconds.' > >> write(*,*)ftot_ > > I think you want to print here ftot_ - otherwise, calculating the second > loop takes 0.0000 seconds ;-) > > > This is what I get with Intel's compiler on a 2GHz PC. Msybe you need > > to upgrade? > > > Analysis Runs for 0.1050000 Seconds. > > -19999999.9990236 > > DNAD Runs for 0.1040000 Seconds. > > -19999999.9990236 > > Using: > > $ gfortran -Ofast -march=native -flto -fwhole-program test.f90 > > I get on my dated AMD64: > > $ ./a.out > Analysis Runs for 0.11900000 Seconds. > -19999999.999023605 > DNAD Runs for 8.29999968E-02 Seconds. > -19999999.999023605 24999999.999999996 > > (Actually, the crucial option is -O1 and -fwhole-file, which exists > since 4.5 and presumably will become default in 4.6. That option is > enabled implicitly via -flto. The additional -fwhole-program only > reduces the file size by a small amount, -march=native can never harm > and -Ofast is identically to -O3 -ffast-math.) > > Tobias I get the following error message after I execute: gfortran -Ofast - march=native -flto -fwhole-program test.f90 f951.exe: error: invalid option argument '-Ofast' f951.exe: error: unrecognized command line option "-flto" Fatal Error: Option -fwhole-program is not supported for Fortran gfortran: Internal error: Aborted (program f951) Please submit a full bug report. See <http://gcc.gnu.org/bugs.html> for instructions. gfortran -v Using built-in specs. Target: i586-pc-mingw32 Configured with: ../gcc-trunk/configure --prefix=/mingw --enable- languages=c,for tran --with-gmp=/home/FX/gfortran/dependencies --disable-werror -- enable-threads --disable-nls --build=i586-pc-mingw32 --enable-libgomp --disable- shared --disab le-win32-registry --with-dwarf2 --disable-sjlj-exceptions Thread model: win32 gcc version 4.5.0 20090421 (experimental) [trunk revision 146519] (GCC) I downloaded gfortran from http://mingw-w64.sourceforge.net/. Where can I download a more recent build version of gfortran for WinXP? Thanks. |