source: trunk/examples/extended/electromagnetic/TestEm11/geant3/src/uglast.F@ 1036

Last change on this file since 1036 was 807, checked in by garnier, 17 years ago

update

File size: 3.3 KB
Line 
1
2 SUBROUTINE UGLAST
3*
4* Termination routine to print histograms and statistics
5*
6#include "geant321/gcflag.inc"
7#include "geant321/gckine.inc"
8#include "geant321/gctrak.inc"
9#include "calor.inc"
10#include "celoss.inc"
11#include "histo.inc"
12*
13 CHARACTER*20 parnam,matnam
14 CHARACTER*4 unit1,unit2
15*
16* *** run summary
17 PRINT 749
18 call GFPART (Ikine,parnam,ityp,dum,duc,dut,udu,idu)
19 call GFMATE (Imat ,matnam,dua,duz,dud,dur,dui,udu,idu)
20 CALL GEVKEV (pkine(1),Ekine,unit1)
21 PRINT 750, Ievent,parnam,Ekine,unit1,sizeX,matnam
22 PRINT 749
23*
24 fnorm = 1./Ievent
25*
26* *** total energy deposit
27 Etot = fnorm*Etot
28 Etot2 = fnorm*Etot2
29 rms = sqrt(abs(Etot2-Etot**2))
30*
31 CALL GEVKEV (Etot,aveE,unit1)
32 CALL GEVKEV (rms ,rmsE ,unit2)
33 PRINT 752, aveE,unit1,rmsE,unit2
34*
35* *** track length of primary track
36 TrLen = fnorm*TrLen
37 TrLen2 = fnorm*TrLen2
38 rms = sqrt(abs(TrLen2-TrLen**2))
39 PRINT 753, TrLen,rms
40*
41* *** compare with csda range from table
42 call GFTMAT(Imat,ikine,'RANG',1,pkine(1),csdaRang,dum,ixst)
43 PRINT 763, csdaRang
44*
45* *** projected range of primary track
46 XTrLen = fnorm*XTrLen
47 XTrLen2 = fnorm*XTrLen2
48 rms = sqrt(abs(XTrLen2-XTrLen**2))
49 PRINT 754, XTrLen,rms
50*
51* *** nb of steps and step size of primary track
52 fNbStep = fnorm*NbStep
53 fNbStep2 = fnorm*NbStep2
54 rms1 = sqrt(abs(fNbStep2-fNbStep**2))
55*
56 StepLen = fnorm*StepLen
57 StepLen2 = fnorm*StepLen2
58 rms2 = sqrt(abs(StepLen2-StepLen**2))
59 PRINT 755, fNbStep,rms1,StepLen,rms2
60*
61* *** transmission coefficients
62 absorbed = fnorm*100*kcoef(1)
63 transmit = fnorm*100*kcoef(2)
64 reflected = fnorm*100*kcoef(3)
65 PRINT 756, absorbed, transmit, reflected
66*
67 PRINT 749
68*
69* *** geant termination
70 CALL GLAST
71*
72* *** close HIGZ
73 CALL HPLEND
74*
75* *** Save histo
76 if (iswit(2).eq.1) then
77 write(6,99) fileName
7899 format(/,15x,'histogram file --> Name: ',A25)
79 CALL HRPUT(0,fileName,'N')
80 endif
81*
82* *** formats
83 749 FORMAT(/, 60(1H-),/)
84 750 FORMAT( 1X,'The run is',I8,1X,A10,' of',F8.2,A4,' through ',
85 & E12.4,' cm of ',A10)
86 752 FORMAT( 1X,'Total Energy deposited = ',
87 & F8.3, A4,' +- ', F8.3, A4)
88 753 FORMAT(/,1X,'Track length of primary track = ',
89 & E12.5,' cm +- ', E12.5,' cm')
90 763 FORMAT( 1X,'csda Range from table = ',
91 & E12.5,' cm')
92 754 FORMAT(/,1X,'Projected range = ',
93 & E12.5,' cm +- ', E12.5,' cm')
94 755 FORMAT(/,1X,'Nb of steps of primary track = ',
95 & F6.2,' +- ', F6.2,
96 & 3X,'Step size = ', E12.5,' cm +- ', E12.5,' cm')
97 756 FORMAT(/,1X,'absorbed = ',F6.2,' %',3X,'transmit = ', F6.2,' %',
98 & 3X,'reflected = ', F6.2,' %')
99*
100 END
Note: See TracBrowser for help on using the repository browser.