source: trunk/examples/extended/electromagnetic/TestEm5/geant3/src/gustep.F @ 1330

Last change on this file since 1330 was 807, checked in by garnier, 16 years ago

update

File size: 1.6 KB
Line 
1
2      SUBROUTINE GUSTEP
3*
4#include "geant321/gcflag.inc"
5#include "geant321/gckine.inc"
6#include "geant321/gcking.inc"
7#include "geant321/gconst.inc"
8#include "geant321/gctmed.inc"
9#include "geant321/gctrak.inc"
10*
11#include "runinfo.inc"
12#include "histo.inc"
13*                                                                               
14*                                                                               
15* *** Debug event and store tracks for drawing
16      IF (IDEBUG.NE.0)   CALL GPCXYZ     
17      IF ((ISWIT(1).EQ.1).AND.(CHARGE.NE.0.)) CALL GSXYZ
18      IF  (ISWIT(1).EQ.2)                     CALL GSXYZ                       
19*
20* *** collect informations in the absorber only
21*
22      if (numed.ne.1) return
23*
24*     energy deposit
25      edep = edep + destep
26*
27*     number of steps and total track length
28      if (charge.ne.0.) then
29        stpch = stpch + 1.
30        trkch = trkch + step
31      else
32        stpne = stpne + 1.
33        trkne = trkne + step
34      endif                         
35*
36*     manage secondaries
37      if (ngkine.gt.0) then
38        do k = 1,ngkine
39          energy = gkin(4,k)
40          id     = gkin(5,k)
41          if (id.eq.1) then
42            ngamma = ngamma + 1
43            if (histo(3)) call hfill(3,log10(1000*energy),0.,1.)
44          else if (id.eq.2) then
45            nposit = nposit + 1
46            energy = energy - emass
47            if (histo(2)) call hfill(2,energy/histUnit(2),0.,1.)
48          else if (id.eq.3) then
49            nelect = nelect + 1
50            energy = energy - emass
51            if (histo(2)) call hfill(2,energy/histUnit(2),0.,1.)
52          endif             
53        enddo
54*       keep or kill all secondaries   
55        if (.not.kill) call gsking(0)
56      endif     
57*
58      END
Note: See TracBrowser for help on using the repository browser.