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

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

update

File size: 1.8 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/gconst.inc"
10#include "geant321/gctrak.inc"
11#include "geant321/gctmed.inc"
12#include "geant321/gcvolu.inc"
13#include "calor.inc"
14#include "celoss.inc"
15#include "histo.inc"
16*
17      data aMeV /1.e-3/
18*
19* *** Debug event and store tracks for drawing
20      IF (IDEBUG.NE.0)   CALL GPCXYZ     
21      IF ((ISWIT(1).EQ.1).AND.(CHARGE.NE.0.)) CALL GSXYZ
22      IF  (ISWIT(1).EQ.2)                     CALL GSXYZ
23*
24* *** Something generated ?
25      IF(NGKINE.GT.0) CALL GSKING(0)
26*
27* *** Energy deposited and charged track length
28      IF (NUMED.LE.NbAbsor) THEN
29        if (DESTEP.NE.0.)      EdepAbs(NUMED) = EdepAbs(NUMED) + DESTEP
30        if (CHARGE*STEP.NE.0.) TrckAbs(NUMED) = TrckAbs(NUMED) + STEP
31*       longitudinal profile of Edep
32        layer = number(nlevel-1)
33        ih = MaxAbs + numed
34        if (histo(ih)) call hfill (ih,0.+layer,0.,destep/(aMeV*nevent))         
35      ENDIF
36*
37* *** Energy flow : leaving an absorber ?
38      IF ((NUMED.LE.NbAbsor).and.(INWVOL.eq.2)) THEN
39        Idnow = NbAbsor*(layer-1) + numed
40        Eflow = gekin
41        if (ipart.eq.2) Eflow = gekin + 2*emass
42*                     
43        if (max(abs(vect(2)),abs(vect(3))).ge.(0.5*calorYZ)) then
44          EleakLat(Idnow)   = EleakLat(Idnow)   + Eflow
45        elseif (vect(4).ge.0.) then
46          EnerFlow(Idnow+1) = EnerFlow(Idnow+1) + Eflow
47        else
48          EnerFlow(Idnow)   = EnerFlow(Idnow)   - Eflow   
49        endif
50      ENDIF         
51*
52      END
Note: See TracBrowser for help on using the repository browser.