/[PAMELA software]/DarthVader/ToFLevel2/src/toftrk.for
ViewVC logotype

Diff of /DarthVader/ToFLevel2/src/toftrk.for

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 1.8 by mocchiut, Mon Jan 22 10:45:26 2007 UTC revision 1.10 by mocchiut, Wed Feb 7 08:17:17 2007 UTC
# Line 24  C  jan-07 WM: in the xtofpos calculation Line 24  C  jan-07 WM: in the xtofpos calculation
24  C             inserted. In the old code one would still calculate a  C             inserted. In the old code one would still calculate a
25  C             xtofpos-value even if the TDC information was missing  C             xtofpos-value even if the TDC information was missing
26  C  jan-07 WM: flag for PMTs #10 and #35 added, TDC=819 due to bit-shift  C  jan-07 WM: flag for PMTs #10 and #35 added, TDC=819 due to bit-shift
27  C  C  jan-05 WM: bug fixed: calculation of zenith angles using DOTRACK2
28    C             was incorrect
29    C  jan-07 WM: bug fixed: in some cases tdc_tw was calculated due to a
30    C             leftover "xhelp" value
31  C****************************************************************************  C****************************************************************************
32        IMPLICIT NONE        IMPLICIT NONE
33  C      C    
# Line 53  c     define TOF Z-coordinates Line 56  c     define TOF Z-coordinates
56    
57    
58        INTEGER IFAIL        INTEGER IFAIL
59  c      REAL dx,dy,dr,xdummy  c      REAL dx,dy,dr
60        REAL ds        REAL ds
61        REAL t1,t2,t3,t4        REAL t1,t2,t3,t4
62        REAL yhelp,xhelp,xhelp1,xhelp2        REAL yhelp,xhelp,xhelp1,xhelp2
# Line 145  C  ratio helium to proton ca. 4 Line 148  C  ratio helium to proton ca. 4
148    
149        pmt_id=0        pmt_id=0
150    
151          do j=1,6
152          THXOUT(j) = 0.
153          THYOUT(j) = 0.
154          enddo
155    
156  C----------------------------------------------------------------------  C----------------------------------------------------------------------
157  C-------------------------get ToF data --------------------------------  C-------------------------get ToF data --------------------------------
158  C     we cannot use the tofxx(x,x,x)  data  from tofl2com since it is  C     we cannot use the tofxx(x,x,x)  data  from tofl2com since it is
# Line 257  C     COPY THE ALFA VECTOR FROM AL_PP TO Line 265  C     COPY THE ALFA VECTOR FROM AL_PP TO
265           AL_P(i) = al_pp(i)           AL_P(i) = al_pp(i)
266        enddo        enddo
267    
268  c     write(*,*) AL_P  c      write(*,*) AL_P
269    
270        if (al_p(5).eq.0.) THEN        if (al_p(5).eq.0.) THEN
271           PRINT *,' TOF - WARNING F77: track with R = 0, discarded'           PRINT *,' TOF - WARNING F77: track with R = 0, discarded'
# Line 279  C     write(*,*) (TLOUT(i),i=1,6) Line 287  C     write(*,*) (TLOUT(i),i=1,6)
287    
288   969  continue   969  continue
289    
290    C---  convert  angles to radian
291          do j=1,6
292          THXOUT(j) = 3.1415927*THXOUT(j)/180.
293          THYOUT(j) = 3.1415927*THYOUT(j)/180.
294          enddo
295    
296          do j=1,6
297    c      write (*,*) j,THXOUT(j),THYOUT(j)
298          enddo
299    
300    
301  C----------------------------------------------------------------------  C----------------------------------------------------------------------
302  C------------------  set ADC & TDC flag = 0    ------------------------  C------------------  set ADC & TDC flag = 0    ------------------------
# Line 627  C----------------------------S1 -------- Line 645  C----------------------------S1 --------
645        IF (tof11_i.GT.none_find.AND.abs(yout(1)).lt.100) THEN        IF (tof11_i.GT.none_find.AND.abs(yout(1)).lt.100) THEN
646           i = tof11_i           i = tof11_i
647           if (tof11(left,i,iadc).eq.4095) then           if (tof11(left,i,iadc).eq.4095) then
648              phi   = atan(tan(THXOUT(1))/tan(THYOUT(1)))              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))
 c            theta = atan(tan(THXOUT(1))/cos(phi)  
649              theta = atan(tan(THXOUT(1))/cos(phi))              theta = atan(tan(THXOUT(1))/cos(phi))
650              xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))              xkorr=adcx11(left,i,1)*exp(-yhelp/adcx11(left,i,2))
651              xkorr=xkorr/hepratio                          xkorr=xkorr/hepratio            
# Line 636  c            theta = atan(tan(THXOUT(1)) Line 653  c            theta = atan(tan(THXOUT(1))
653              adcflag(ch11a(i),hb11a(i)) = 1              adcflag(ch11a(i),hb11a(i)) = 1
654           endif           endif
655           if (tof11(right,i,iadc).eq.4095) then           if (tof11(right,i,iadc).eq.4095) then
656              phi   = atan(tan(THXOUT(1))/tan(THYOUT(1)))              phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))
 c            theta = atan(tan(THXOUT(1))/cos(phi)  
657              theta = atan(tan(THXOUT(1))/cos(phi))              theta = atan(tan(THXOUT(1))/cos(phi))
658              xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))              xkorr=adcx11(right,i,1)*exp(yhelp/adcx11(right,i,2))
659              xkorr=xkorr/hepratio                          xkorr=xkorr/hepratio            
# Line 650  c            theta = atan(tan(THXOUT(1)) Line 666  c            theta = atan(tan(THXOUT(1))
666        IF (tof12_i.GT.none_find.AND.abs(xout(2)).lt.100) THEN        IF (tof12_i.GT.none_find.AND.abs(xout(2)).lt.100) THEN
667           i = tof12_i           i = tof12_i
668           if (tof12(left,i,iadc).eq.4095) then           if (tof12(left,i,iadc).eq.4095) then
669              phi   = atan(tan(THXOUT(2))/tan(THYOUT(2)))              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))
 c            theta = atan(tan(THXOUT(2))/cos(phi)  
670              theta = atan(tan(THXOUT(2))/cos(phi))              theta = atan(tan(THXOUT(2))/cos(phi))
671              xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))              xkorr=adcx12(left,i,1)*exp(-xhelp/adcx12(left,i,2))
672              xkorr=xkorr/hepratio                          xkorr=xkorr/hepratio            
# Line 659  c            theta = atan(tan(THXOUT(2)) Line 674  c            theta = atan(tan(THXOUT(2))
674              adcflag(ch12a(i),hb12a(i)) = 1              adcflag(ch12a(i),hb12a(i)) = 1
675           endif           endif
676           if (tof12(right,i,iadc).eq.4095) then           if (tof12(right,i,iadc).eq.4095) then
677              phi   = atan(tan(THXOUT(2))/tan(THYOUT(2)))              phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))
 c            theta = atan(tan(THXOUT(2))/cos(phi)  
678              theta = atan(tan(THXOUT(2))/cos(phi))              theta = atan(tan(THXOUT(2))/cos(phi))
679              xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))              xkorr=adcx12(right,i,1)*exp(xhelp/adcx12(right,i,2))
680              xkorr=xkorr/hepratio                          xkorr=xkorr/hepratio            
# Line 675  C-----------------------------S2 ------- Line 689  C-----------------------------S2 -------
689        IF (tof21_i.GT.none_find.AND.abs(xout(3)).lt.100) THEN        IF (tof21_i.GT.none_find.AND.abs(xout(3)).lt.100) THEN
690           i = tof21_i           i = tof21_i
691           if (tof21(left,i,iadc).eq.4095) then           if (tof21(left,i,iadc).eq.4095) then
692              phi   = atan(tan(THXOUT(3))/tan(THYOUT(3)))              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))
 c            theta = atan(tan(THXOUT(3))/cos(phi)  
693              theta = atan(tan(THXOUT(3))/cos(phi))              theta = atan(tan(THXOUT(3))/cos(phi))
694              xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))              xkorr=adcx21(left,i,1)*exp(-xhelp/adcx21(left,i,2))
695              xkorr=xkorr/hepratio                          xkorr=xkorr/hepratio            
# Line 684  c            theta = atan(tan(THXOUT(3)) Line 697  c            theta = atan(tan(THXOUT(3))
697              adcflag(ch21a(i),hb21a(i)) = 1              adcflag(ch21a(i),hb21a(i)) = 1
698           endif           endif
699           if (tof21(right,i,iadc).eq.4095) then           if (tof21(right,i,iadc).eq.4095) then
700              phi   = atan(tan(THXOUT(3))/tan(THYOUT(3)))              phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))
 c            theta = atan(tan(THXOUT(3))/cos(phi)  
701              theta = atan(tan(THXOUT(3))/cos(phi))              theta = atan(tan(THXOUT(3))/cos(phi))
702              xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))              xkorr=adcx21(right,i,1)*exp(xhelp/adcx21(right,i,2))
703              xkorr=xkorr/hepratio                          xkorr=xkorr/hepratio            
# Line 699  c            theta = atan(tan(THXOUT(3)) Line 711  c            theta = atan(tan(THXOUT(3))
711        IF (tof22_i.GT.none_find.AND.abs(yout(4)).lt.100) THEN        IF (tof22_i.GT.none_find.AND.abs(yout(4)).lt.100) THEN
712           i = tof22_i           i = tof22_i
713           if (tof22(left,i,iadc).eq.4095) then           if (tof22(left,i,iadc).eq.4095) then
714              phi   = atan(tan(THXOUT(4))/tan(THYOUT(4)))              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))
 c            theta = atan(tan(THXOUT(4))/cos(phi)  
715              theta = atan(tan(THXOUT(4))/cos(phi))              theta = atan(tan(THXOUT(4))/cos(phi))
716              xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))              xkorr=adcx22(left,i,1)*exp(-yhelp/adcx22(left,i,2))
717              xkorr=xkorr/hepratio                          xkorr=xkorr/hepratio            
# Line 708  c            theta = atan(tan(THXOUT(4)) Line 719  c            theta = atan(tan(THXOUT(4))
719              adcflag(ch22a(i),hb22a(i)) = 1              adcflag(ch22a(i),hb22a(i)) = 1
720           endif           endif
721           if (tof22(right,i,iadc).eq.4095) then           if (tof22(right,i,iadc).eq.4095) then
722              phi   = atan(tan(THXOUT(4))/tan(THYOUT(4)))              phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))
 c            theta = atan(tan(THXOUT(4))/cos(phi)  
723              theta = atan(tan(THXOUT(4))/cos(phi))              theta = atan(tan(THXOUT(4))/cos(phi))
724              xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))              xkorr=adcx22(right,i,1)*exp(yhelp/adcx22(right,i,2))
725              xkorr=xkorr/hepratio                          xkorr=xkorr/hepratio            
# Line 724  C-----------------------------S3 ------- Line 734  C-----------------------------S3 -------
734        IF (tof31_i.GT.none_find.AND.abs(yout(5)).lt.100) THEN        IF (tof31_i.GT.none_find.AND.abs(yout(5)).lt.100) THEN
735           i = tof31_i           i = tof31_i
736           if (tof31(left,i,iadc).eq.4095) then           if (tof31(left,i,iadc).eq.4095) then
737              phi   = atan(tan(THXOUT(5))/tan(THYOUT(5)))              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))
 c            theta = atan(tan(THXOUT(5))/cos(phi)  
738              theta = atan(tan(THXOUT(5))/cos(phi))              theta = atan(tan(THXOUT(5))/cos(phi))
739              xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))              xkorr=adcx31(left,i,1)*exp(-yhelp/adcx31(left,i,2))
740              xkorr=xkorr/hepratio                          xkorr=xkorr/hepratio            
# Line 733  c            theta = atan(tan(THXOUT(5)) Line 742  c            theta = atan(tan(THXOUT(5))
742              adcflag(ch31a(i),hb31a(i)) = 1              adcflag(ch31a(i),hb31a(i)) = 1
743           endif           endif
744           if (tof31(right,i,iadc).eq.4095) then           if (tof31(right,i,iadc).eq.4095) then
745              phi   = atan(tan(THXOUT(5))/tan(THYOUT(5)))              phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))
 c            theta = atan(tan(THXOUT(5))/cos(phi)    
746              theta = atan(tan(THXOUT(5))/cos(phi))              theta = atan(tan(THXOUT(5))/cos(phi))
747              xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))              xkorr=adcx31(right,i,1)*exp(yhelp/adcx31(right,i,2))
748              xkorr=xkorr/hepratio                          xkorr=xkorr/hepratio            
# Line 748  c            theta = atan(tan(THXOUT(5)) Line 756  c            theta = atan(tan(THXOUT(5))
756        IF (tof32_i.GT.none_find.AND.abs(xout(6)).lt.100) THEN        IF (tof32_i.GT.none_find.AND.abs(xout(6)).lt.100) THEN
757           i = tof32_i           i = tof32_i
758           if (tof32(left,i,iadc).eq.4095) then           if (tof32(left,i,iadc).eq.4095) then
759              phi   = atan(tan(THXOUT(6))/tan(THYOUT(6)))              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))
 c            theta = atan(tan(THXOUT(6))/cos(phi)  
760              theta = atan(tan(THXOUT(6))/cos(phi))              theta = atan(tan(THXOUT(6))/cos(phi))
761              xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))              xkorr=adcx32(left,i,1)*exp(-xhelp/adcx32(left,i,2))
762              xkorr=xkorr/hepratio                          xkorr=xkorr/hepratio            
# Line 757  c            theta = atan(tan(THXOUT(6)) Line 764  c            theta = atan(tan(THXOUT(6))
764              adcflag(ch32a(i),hb32a(i)) = 1              adcflag(ch32a(i),hb32a(i)) = 1
765           endif           endif
766           if (tof32(right,i,iadc).eq.4095) then           if (tof32(right,i,iadc).eq.4095) then
767              phi   = atan(tan(THXOUT(6))/tan(THYOUT(6)))              phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))
 c            theta = atan(tan(THXOUT(6))/cos(phi)  
768              theta = atan(tan(THXOUT(6))/cos(phi))              theta = atan(tan(THXOUT(6))/cos(phi))
769              xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))              xkorr=adcx32(right,i,1)*exp(xhelp/adcx32(right,i,2))
770              xkorr=xkorr/hepratio                          xkorr=xkorr/hepratio            
# Line 852  C--------------------------------------- Line 858  C---------------------------------------
858  C--------------------Time walk correction  -------------------------  C--------------------Time walk correction  -------------------------
859  C--------------------------------------------------------------------  C--------------------------------------------------------------------
860    
861    
862        DO i=1,8        DO i=1,8
863             xhelp= 0.
864           xhelp_a = tof11(left,i,iadc)           xhelp_a = tof11(left,i,iadc)
865           xhelp_t = tof11(left,i,itdc)           xhelp_t = tof11(left,i,itdc)
866           if(xhelp_a<4095) xhelp = tw11(left,i)/sqrt(xhelp_a)           if(xhelp_a<4095) xhelp = tw11(left,i)/sqrt(xhelp_a)
# Line 866  C--------------------------------------- Line 874  C---------------------------------------
874        ENDDO        ENDDO
875    
876        DO i=1,6        DO i=1,6
877             xhelp= 0.
878           xhelp_a = tof12(left,i,iadc)           xhelp_a = tof12(left,i,iadc)
879           xhelp_t = tof12(left,i,itdc)           xhelp_t = tof12(left,i,itdc)
880           if(xhelp_a<4095) xhelp = tw12(left,i)/sqrt(xhelp_a)           if(xhelp_a<4095) xhelp = tw12(left,i)/sqrt(xhelp_a)
# Line 879  C--------------------------------------- Line 888  C---------------------------------------
888        ENDDO        ENDDO
889  C----  C----
890        DO i=1,2        DO i=1,2
891             xhelp= 0.
892           xhelp_a = tof21(left,i,iadc)           xhelp_a = tof21(left,i,iadc)
893           xhelp_t = tof21(left,i,itdc)           xhelp_t = tof21(left,i,itdc)
894           if(xhelp_a<4095) xhelp = tw21(left,i)/sqrt(xhelp_a)           if(xhelp_a<4095) xhelp = tw21(left,i)/sqrt(xhelp_a)
# Line 892  C---- Line 902  C----
902        ENDDO        ENDDO
903    
904        DO i=1,2        DO i=1,2
905             xhelp= 0.
906           xhelp_a = tof22(left,i,iadc)           xhelp_a = tof22(left,i,iadc)
907           xhelp_t = tof22(left,i,itdc)           xhelp_t = tof22(left,i,itdc)
908           if(xhelp_a<4095) xhelp = tw22(left,i)/sqrt(xhelp_a)           if(xhelp_a<4095) xhelp = tw22(left,i)/sqrt(xhelp_a)
# Line 906  C---- Line 917  C----
917  C----  C----
918    
919        DO i=1,3        DO i=1,3
920             xhelp= 0.
921           xhelp_a = tof31(left,i,iadc)           xhelp_a = tof31(left,i,iadc)
922           xhelp_t = tof31(left,i,itdc)           xhelp_t = tof31(left,i,itdc)
923           if(xhelp_a<4095) xhelp = tw31(left,i)/sqrt(xhelp_a)           if(xhelp_a<4095) xhelp = tw31(left,i)/sqrt(xhelp_a)
# Line 919  C---- Line 931  C----
931        ENDDO        ENDDO
932    
933        DO i=1,3        DO i=1,3
934             xhelp= 0.
935           xhelp_a = tof32(left,i,iadc)           xhelp_a = tof32(left,i,iadc)
936           xhelp_t = tof32(left,i,itdc)           xhelp_t = tof32(left,i,itdc)
937           if(xhelp_a<4095) xhelp = tw32(left,i)/sqrt(xhelp_a)           if(xhelp_a<4095) xhelp = tw32(left,i)/sqrt(xhelp_a)
# Line 939  C-----------------angle and ADC(x) corre Line 952  C-----------------angle and ADC(x) corre
952  C-----------------------------S1 -------------------------------------  C-----------------------------S1 -------------------------------------
953    
954        yhelp=yout(1)        yhelp=yout(1)
955        phi   = atan(tan(THXOUT(1))/tan(THYOUT(1)))  
956  c      theta = atan(tan(THXOUT(1))/cos(phi)        phi   = atan(tan(THYOUT(1))/tan(THXOUT(1)))
957        theta = atan(tan(THXOUT(1))/cos(phi))        theta = atan(tan(THXOUT(1))/cos(phi))
958    
959        IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN        IF (tof11_i.GT.none_find.AND.yhelp.lt.100) THEN
# Line 965  c      theta = atan(tan(THXOUT(1))/cos(p Line 978  c      theta = atan(tan(THXOUT(1))/cos(p
978    
979    
980        xhelp=xout(2)        xhelp=xout(2)
981        phi   = atan(tan(THXOUT(2))/tan(THYOUT(2)))        phi   = atan(tan(THYOUT(2))/tan(THXOUT(2)))
 c      theta = atan(tan(THXOUT(2))/cos(phi)  
982        theta = atan(tan(THXOUT(2))/cos(phi))        theta = atan(tan(THXOUT(2))/cos(phi))
983    c      write(*,*) 'theta12 ',theta
984        IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN        IF (tof12_i.GT.none_find.AND.xhelp.lt.100) THEN
985    
986           i = tof12_i           i = tof12_i
# Line 989  c      theta = atan(tan(THXOUT(2))/cos(p Line 1002  c      theta = atan(tan(THXOUT(2))/cos(p
1002  C-----------------------------S2 --------------------------------  C-----------------------------S2 --------------------------------
1003    
1004        xhelp=xout(3)        xhelp=xout(3)
1005        phi   = atan(tan(THXOUT(3))/tan(THYOUT(3)))        phi   = atan(tan(THYOUT(3))/tan(THXOUT(3)))
 c      theta = atan(tan(THXOUT(3))/cos(phi)  
1006        theta = atan(tan(THXOUT(3))/cos(phi))        theta = atan(tan(THXOUT(3))/cos(phi))
1007    c      write(*,*) 'theta21 ',theta
1008        IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN        IF (tof21_i.GT.none_find.AND.xhelp.lt.100) THEN
1009    
1010           i = tof21_i           i = tof21_i
# Line 1011  c      theta = atan(tan(THXOUT(3))/cos(p Line 1024  c      theta = atan(tan(THXOUT(3))/cos(p
1024        ENDIF        ENDIF
1025    
1026        yhelp=yout(4)        yhelp=yout(4)
1027        phi   = atan(tan(THXOUT(4))/tan(THYOUT(4)))        phi   = atan(tan(THYOUT(4))/tan(THXOUT(4)))
 c      theta = atan(tan(THXOUT(4))/cos(phi)  
1028        theta = atan(tan(THXOUT(4))/cos(phi))        theta = atan(tan(THXOUT(4))/cos(phi))
1029    c      write(*,*) 'theta22 ',theta
1030    
1031        IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN        IF (tof22_i.GT.none_find.AND.yhelp.lt.100) THEN
1032    
# Line 1036  c      theta = atan(tan(THXOUT(4))/cos(p Line 1049  c      theta = atan(tan(THXOUT(4))/cos(p
1049  C-----------------------------S3 --------------------------------  C-----------------------------S3 --------------------------------
1050    
1051        yhelp=yout(5)        yhelp=yout(5)
1052        phi   = atan(tan(THXOUT(5))/tan(THYOUT(5)))        phi   = atan(tan(THYOUT(5))/tan(THXOUT(5)))
 c      theta = atan(tan(THXOUT(5))/cos(phi)  
1053        theta = atan(tan(THXOUT(5))/cos(phi))        theta = atan(tan(THXOUT(5))/cos(phi))
1054    c      write(*,*) 'theta31 ',theta
1055                
1056        IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN        IF (tof31_i.GT.none_find.AND.yhelp.lt.100) THEN
1057    
# Line 1059  c      theta = atan(tan(THXOUT(5))/cos(p Line 1072  c      theta = atan(tan(THXOUT(5))/cos(p
1072        ENDIF        ENDIF
1073    
1074        xhelp=xout(6)        xhelp=xout(6)
1075        phi   = atan(tan(THXOUT(6))/tan(THYOUT(6)))        phi   = atan(tan(THYOUT(6))/tan(THXOUT(6)))
 c      theta = atan(tan(THXOUT(6))/cos(phi)  
1076        theta = atan(tan(THXOUT(6))/cos(phi))        theta = atan(tan(THXOUT(6))/cos(phi))
1077    c      write(*,*) 'theta32 ',theta
1078    
1079        IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN        IF (tof32_i.GT.none_find.AND.xhelp.lt.100) THEN
1080    

Legend:
Removed from v.1.8  
changed lines
  Added in v.1.10

  ViewVC Help
Powered by ViewVC 1.1.23