--- DarthVader/TrackerLevel2/src/F77/grkuta.f 2006/11/08 16:42:28 1.3 +++ DarthVader/TrackerLevel2/src/F77/grkuta.f 2007/11/27 11:43:51 1.6 @@ -28,6 +28,7 @@ C. ****************************************************************** C. IMPLICIT DOUBLE PRECISION(A-H,O-Z) + COMMON/DELTAB/DELTA0,DELTA1 * REAL VVV(3),FFF(3) REAL*8 CHARGE, STEP, VECT(*), VOUT(*), F(4) @@ -43,11 +44,14 @@ PARAMETER (PISQUA=.986960440109D+01) PARAMETER (IX=1,IY=2,IZ=3,IPX=4,IPY=5,IPZ=6) + REAL*8 DELTAB(3) + *. *. ------------------------------------------------------------------ *. * This constant is for units CM,GEV/C and KGAUSS * + ITER = 0 NCUT = 0 DO 10 J=1,7 @@ -69,6 +73,9 @@ DO I=1,3 F(I)=DBLE(FFF(I)) ENDDO + DELTAB(2) = -F(2)*VECT(7)*CHARGE*(DELTA0+DELTA1*VVV(2)) + F(2) = F(2)+DELTAB(2) +cPP ----------------- * * Start of integration * @@ -106,7 +113,10 @@ CALL GUFLD(VVV,FFF) DO I=1,3 F(I)=DBLE(FFF(I)) - ENDDO + ENDDO + DELTAB(2) = -F(2)*VECT(7)*CHARGE*(DELTA0+DELTA1*VVV(2)) + F(2) = F(2)+DELTAB(2) +cPP ----------------- C CALL GUFLD(XYZT,F) AT = A + SECXS(1) BT = B + SECYS(1) @@ -141,6 +151,9 @@ DO I=1,3 F(I)=DBLE(FFF(I)) ENDDO + DELTAB(2) = -F(2)*VECT(7)*CHARGE*(DELTA0+DELTA1*VVV(2)) + F(2) = F(2)+DELTAB(2) +cPP ----------------- C CALL GUFLD(XYZT,F) * Z = Z + (C + (SECZS(1) + SECZS(2) + SECZS(3)) * THIRD) * H @@ -500,8 +513,8 @@ $ +(VOUT(IY)-VECT(IY))**2 $ +(VOUT(IZ)-VECT(IZ))**2 $ ) - print*,'WARNING: GRKUTA2 --> ' - $ ,'helix :-( ... length evaluated with straight line' +c print*,'WARNING: GRKUTA2 --> ' +c $ ,'helix :-( ... length evaluated with straight line' * 999 END @@ -521,18 +534,17 @@ real*8 vv(3),ff(3) !inter_B.f works in double precision - do i=1,3 - vv(i)=v(i)/100. !inter_B.f works in meters - enddo -c inter_B: coordinates in m, B field in Tesla -c print*,'GUFLD: v ',v - call inter_B(vv(1),vv(2),vv(3),ff) - do i=1,3 !change back the field in kGauss - f(i)=ff(i)*10. - enddo -c print*,'GUFLD: b ',f -c print*,vv,ff - + do i=1,3 + vv(i)=v(i)/100. !inter_B.f works in meters + enddo +c inter_B: coordinates in m, B field in Tesla +c$$$ print*,'GUFLD: v ',v + call inter_B(vv(1),vv(2),vv(3),ff) + do i=1,3 !change back the field in kGauss + f(i)=ff(i)*10. + enddo +c$$$ print*,'GUFLD: b ',f + return end