Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

OTHER THAN NONE OPTIMIZE PROBLEM

cacciatore
Beginner
544 Views

Hi

I am using CVF 6.6b in W98SE.A subroutine of a Qwin programis showing a strange behavior, for some particular set of input values to this sub ,in the formula below, when using any optimization other then none :

CC=COSD(EL)*COSD(ELPT)*COSD(DEL)+SIND(EL)*SIND(ELPT) 

when the diference between EL and ELPT is very small, and DEL is very small, CC is greater then 1.0.If I put DEL=0.0 and EL=ELPT before the formula, just for test,CC is calculated as1.0 as it should be (cos2+sin2=1)

The problem does not occurs if I comment the line commented with !!!!!!!!!!! in the code below. This line is not even accessed when the problem occurs becauseI am not using a 760 antena type (TIPOANT).

Also no problem if I calculate CC in the ANGULO sub.

I could live with no optimiztions butwillnever be sure results are 100% ok.

This problemseemswell beyond my small Fortran knowledge so I would appreciate any help.

Thanks, Geraldo

(Is it really necessary to make all variables=0.0 ?)

SUBROUTINE ANG_E_D(XANTE,YANTE,ALTU,AZANTE,EL,X,Y,ANG,D,ELPT,ANGV,AZPROJ)
USE MODAN303
IMPLICIT NONE
REAL*4 M,MYA,ALTU,DELH,DX,DY,X,Y,ANG,D,ELPT,ANGV,AZPROJ,DXY,AZPT, &
XANTE,YANTE,AZANTE,EL,XA,YA,ZA,DP,DPD,ZPLAN,U,CC,DEL,GRA
 M=0.0;MYA=0.0;DELH=0.0;DX=0.0;DY=0.0;ANG=0.0;D=0.0;ELPT=0.0;ANGV=0.0
AZPROJ=0.0;DXY=0.0;AZPT=0.0;XA=0.0;YA=0.0;ZA=0.0;DP=0.0
DPD=0.0;ZPLAN=0.0;U=0.0;CC=0.0;DEL=0.0;GRA=0.0
GRA=180.0/3.1415929 
DELH=PLAN-ALTU
DX=X-XANTE
DY=Y-YANTE
DXY=SQRT((DX)**2+(DY)**2)
D=SQRT(DXY**2+DELH**2)
IF(ABS(DELH).LE.0.01) THEN
ELPT=0.0
ELSE IF(DXY.LE.0.001) THEN
ELPT=90.0
IF(DELH.LT.0.0) ELPT=-90.0
ELSE
ELPT=GRA*ATAN(DELH/DXY)
END IF
IF(DXY.LE.0.001) THEN 
AZPT=AZANTE
ELSE
AZPT=GRA*ASIN(DX/DXY)
IF(DY.LE.0.0.AND.DX.GE.0.0) THEN
AZPT=180.0-AZPT
ELSE IF(DY.GE.0.0.AND.DX.LE.0.0) THEN
AZPT=360.0+AZPT
ELSE IF(DY.LE.0.0.AND.DX.LE.0.0) THEN
AZPT=180.0-AZPT
END IF
END IF
 DEL=AZPT-AZANTE

CC=COSD(EL)*COSD(ELPT)*COSD(DEL)+SIND(EL)*SIND(ELPT)
! CALL ANGULO(EL,ELPT,DEL,CC)
 IF(ABS(CC).GT.1.0) THEN
OPEN(UNIT=1,FILE='C:PROJERRO.TXT',FORM='FORMATTED')
WRITE(1,FMT='(5E20.10)')CC,DEL,AZPT,EL,ELPT
CLOSE(1)
CALL EXIT
END IF
ANG=GRA*ACOS(CC)
IF(DEL.LT.0.0) THEN
DEL=360.0+DEL
END IF
IF(DEL.GT.180.0) THEN
ANG=360.0-ANG
END IF

IF(T IPOANT.EQ.760) THEN ! SETORIAL
IF(D.GT.1.0) THEN
XA=DXY*COSD(DEL)
YA=-DXY*SIND(DEL)
ZA=DELH
!-- CALC ANGV
DP=ABS(XA*SIND(EL)-ZA*COSD(EL))
DPD=DP/D
IF(ABS(DPD).GT.0.99999999) THEN
DPD=0.99999999
END IF
ANGV=GRA*ASIN(DPD) !!!!!!!!!!!
ZPLAN=XA*TAND(EL)
IF(ZA.LT.ZPLAN) THEN
ANGV=-ANGV
END IF
!-- FIM CALC ANGV
!-- CALC AZPROJ
M=D*COSD(ANGV)
IF(M.NE.0.0) THEN
MYA=ABS(YA/M)
IF(MYA.GT.0.9999999999) THEN
MYA=0.9999999999
ELSE
MYA=ABS(YA)/M
END IF
AZPROJ=GRA*ASIN(MYA)
ELSE
AZPROJ=0.0
END IF
!--ENQUADRAMENTO AZPROJ NOS QUADRANTES
U=-ZA*TAND(EL)
IF(XA.GT.U) THEN
IF(YA.GE.0.0) THEN
AZPROJ=360.0-AZPROJ
ELSE IF(YA.LT.0.0) THEN
AZPROJ=AZPROJ
END IF
ELSE IF(XA.LT.U) THEN
IF(YA.GE.0.0) THEN
AZPROJ=180.0+AZPROJ
ELSE IF(YA.LT.0.0) THEN
AZPROJ=180.0-AZPROJ
END IF
ELSE
IF(YA.LT.0.0) THEN
AZPROJ=90.0
ELSE IF(YA.GT.0.0) THEN
AZPROJ=270.0
ELSE ! YA=0.0
AZPROJ=0.0
END IF
END IF
!--FIM ENQUADRAMENTO
ELSE
ANGV=0.0 ! D<=1.0
AZPROJ=0.0
END IF
END IF !! FIM PARA SETORIAL

RETURN
END SUBROUTINE ANG_E_D
!!--------------------------------------------
!SUBROUTINE ANGULO(EL,ELPT,DEL,CC)
!
!IMPLICIT NONE
!REAL*4 EL,ELPT,DEL,CC
!
!CC=0.0
!CC=COSD(EL)*COSD(ELPT)*COSD(DEL)+SIND(EL)*SIND(ELPT)
!RETURN
!END SUBROUTINE ANGULO

0 Kudos
2 Replies
TimP
Honored Contributor III
544 Views
If you are running into numerical problems with optimization, you should be considering the /fltconsistency option, and possibly making it all double precision. Yes, it's a good idea to zero your data explicitly, rather than depending on the behavior of a particular compiler.
0 Kudos
cacciatore
Beginner
544 Views

Tim,

Thanks for yor quick answer.

/fltconsistency alone was not enough. Using double precision solved the issue. To be sure Iam usingboth. Not to make it 'all' to double I just made:

REAL*8 DCC

DCC=DCOSD(DBLE(EL))*DCOSD(DBLE(ELPT))*DCOSD(DBLE(DEL))+ &

DSIND(DBLE(EL)) *DSIND(DBLE(ELPT))

ANG=GRA*DACOS(DCC) ! radian to deg

and this was enough.

Just one more question:

Acording to help foracosd(x),asind(x) and atand(x)

x
(Input) Must be of type real and must be greater than or equal to zero. The |x| must be less than or equal to 1.

I made some tests (not exaustive ones) with x < 0.0 (but |x| < 1.) and the results were apparently correct. It seems strangethe |x| in helpas it is already said x must be > 0.0.Is it 'dangerous' to use those functions with x < 0.0 ? Not to keep converting radians to deg I wouldprefer to always use acosd.

Thanks again

Geraldo

0 Kudos
Reply