source: trunk/examples/extended/electromagnetic/TestEm13/geant3/src/gustep.F @ 1309

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

update

File size: 2.2 KB
Line 
1
2      SUBROUTINE GUSTEP                                                         
3*                                                                               
4*     User routine called at the end of each tracking step           
5*                                                               
6#include "geant321/gcflag.inc"
7#include "geant321/gckine.inc"
8#include "geant321/gcking.inc"
9#include "geant321/gctrak.inc"
10*
11#include "process.inc"
12#include "histo.inc"
13*
14      character*20 cdum                                                             
15*                                                                                                                                                             
16* *** Debug event and store tracks for drawing
17      IF (IDEBUG.NE.0)   CALL GPCXYZ
18      IF (IDEBUG.NE.0)   CALL GPGKIN           
19      IF ((ISWIT(1).EQ.1).AND.(CHARGE.NE.0.)) CALL GSXYZ
20      IF  (ISWIT(1).EQ.2)                     CALL GSXYZ
21*
22* *** if no process: return
23      IF (NMEC.EQ.0) return                                                                                   
24*
25* *** count nb of invoked processes
26      DO IM = 1,NMEC
27        IPROC = LMEC(IM)
28        IF (IPROC.EQ.21) IPROC = 12
29        IF (IPROC.LE.12) NBCALL(IPROC) = NBCALL(IPROC)+1
30      ENDDO
31*
32* *** sum track length for discrete processes
33      if ((iproc.gt.5)) then
34        nbTot    = nbTot + 1
35        sumTrak  = sumTrak  + sleng
36        sumTrak2 = sumTrak2 + sleng*sleng
37      endif
38*
39* *** plot final state
40*
41*     scattered primary particle (if still alive)
42      if (istop.eq.0) then
43        id = 1
44        if (histo(id)) call hfill (id,gekin/histUnit(id),0.,1.)
45        id = 2
46        if (histo(id)) call hfill (id,vect(4),0.,1.)
47      endif
48*     
49* *** secondaries 
50      if (ngkine.gt.0) then
51        do lp = 1,ngkine
52          ipar = gkin(5,lp) + 0.1
53          call gfpart(ipar,cdum,ndum,gmass,gcharg,dum,dum,ndum)
54          ekin = gkin(4,lp) - gmass
55          pc   = sqrt(gkin(1,lp)**2 + gkin(2,lp)**2 + gkin(3,lp)**2)
56          cost = gkin(1,lp)/pc
57          if (gcharg.ne.0.) id = 3
58          if (gcharg.eq.0.) id = 5
59          if (histo(id)) call hfill (id,ekin/histUnit(id),0.,1.)
60          id = id + 1
61          if (histo(id)) call hfill (id,cost,0.,1.)
62        enddo
63      endif           
64*     
65* *** stop the tracking
66      istop = 1                     
67*
68      END
Note: See TracBrowser for help on using the repository browser.