*$ CREATE MGDRAW.FOR *COPY MGDRAW * * *=== mgdraw ===========================================================* * * SUBROUTINE MGDRAW ( ICODE, MREG ) INCLUDE '(DBLPRC)' INCLUDE '(DIMPAR)' INCLUDE '(IOUNIT)' * *----------------------------------------------------------------------* * * * MaGnetic field trajectory DRAWing: actually this entry manages * * all trajectory dumping for * * drawing * * * * Created by Alfredo Ferrari * * INFN - Milan * * last change 10-nov-02 by Alfredo Ferrari * * INFN - Milan * * * *----------------------------------------------------------------------* * INCLUDE '(CASLIM)' INCLUDE '(COMPUT)' INCLUDE '(EPISOR)' INCLUDE '(FHEAVY)' INCLUDE '(FINUC)' INCLUDE '(MGDDCM)' INCLUDE '(PAPROP)' INCLUDE '(STACK)' INCLUDE '(STARS)' INCLUDE '(TRACKR)' * CHARACTER*20 FILNAM LOGICAL LFCOPE SAVE LFCOPE DATA LFCOPE / .FALSE. / * *----------------------------------------------------------------------* * * * Icode = 1: call from Kaskad * * Icode = 2: call from Emfsco * * Icode = 3: call from Kasneu * * Icode = 4: call from Kashea * * Icode = 5: call from Kasoph * * * *----------------------------------------------------------------------* * * IF ( .NOT. LFCOPE ) THEN LFCOPE = .TRUE. IF ( KOMPUT .EQ. 2 ) THEN FILNAM = '/'//CFDRAW(1:8)//' DUMP A' ELSE FILNAM = CFDRAW END IF c OPEN ( UNIT = IODRAW, FILE = FILNAM, STATUS = 'NEW', FORM = c & 'UNFORMATTED' ) END IF if(mtrack.ge.1.and.mreg.eq.3) then if(mtrack.ne.1) then write(*,*) 'alarm mtrack=',mtrack stop endif if(icode.eq.4.and.npheav.ne.1) then write(*,*) 'alarm npheav=',npheav stop endif elostt=elostt+dtrack(1) endif c WRITE (IODRAW) NTRACK, MTRACK, JTRACK, SNGL (ETRACK), c & SNGL (WTRACK) c WRITE (IODRAW) ( SNGL (XTRACK (I)), SNGL (YTRACK (I)), c & SNGL (ZTRACK (I)), I = 0, NTRACK ), c & ( SNGL (DTRACK (I)), I = 1,MTRACK ), c & SNGL (CTRACK) RETURN * *======================================================================* * * * Boundary-(X)crossing DRAWing: * * * * Icode = 1x: call from Kaskad * * 19: boundary crossing * * Icode = 2x: call from Emfsco * * 29: boundary crossing * * Icode = 3x: call from Kasneu * * 39: boundary crossing * * Icode = 4x: call from Kashea * * 49: boundary crossing * * Icode = 5x: call from Kasoph * * 59: boundary crossing * * * *======================================================================* * * ENTRY BXDRAW ( ICODE, MREG, NEWREG, XSCO, YSCO, ZSCO ) RETURN * *======================================================================* * * * Event End DRAWing: * * * *======================================================================* * * ENTRY EEDRAW ( ICODE ) RETURN * *======================================================================* * * * ENergy deposition DRAWing: * * * * Icode = 1x: call from Kaskad * * 10: elastic interaction recoil * * 11: inelastic interaction recoil * * 12: stopping particle * * 13: pseudo-neutron deposition * * 14: escape * * 15: time kill * * Icode = 2x: call from Emfsco * * 20: local energy deposition (i.e. photoelectric) * * 21: below threshold, iarg=1 * * 22: below threshold, iarg=2 * * 23: escape * * 24: time kill * * Icode = 3x: call from Kasneu * * 30: target recoil * * 31: below threshold * * 32: escape * * 33: time kill * * Icode = 4x: call from Kashea * * 40: escape * * 41: time kill * * Icode = 5x: call from Kasoph * * 50: optical photon absorption * * 51: escape * * 52: time kill * * * *======================================================================* * * ENTRY ENDRAW ( ICODE, MREG, RULL, XSCO, YSCO, ZSCO ) IF ( .NOT. LFCOPE ) THEN LFCOPE = .TRUE. IF ( KOMPUT .EQ. 2 ) THEN FILNAM = '/'//CFDRAW(1:8)//' DUMP A' ELSE FILNAM = CFDRAW END IF c OPEN ( UNIT = IODRAW, FILE = FILNAM, STATUS = 'NEW', FORM = c & 'UNFORMATTED' ) END IF c WRITE (IODRAW) 0, ICODE, JTRACK, SNGL (ETRACK), SNGL (WTRACK) c WRITE (IODRAW) SNGL (XSCO), SNGL (YSCO), SNGL (ZSCO), SNGL (RULL) if(mreg.eq.3) then elostt=elostt+rull endif RETURN * *======================================================================* * * * SOurce particle DRAWing: * * * *======================================================================* * ENTRY SODRAW IF ( .NOT. LFCOPE ) THEN LFCOPE = .TRUE. IF ( KOMPUT .EQ. 2 ) THEN FILNAM = '/'//CFDRAW(1:8)//' DUMP A' ELSE FILNAM = CFDRAW END IF write(*,'(a)') & ' event E deposition (MeV)' neve=0 elostt=0 c OPEN ( UNIT = IODRAW, FILE = FILNAM, STATUS = 'NEW', FORM = c & 'UNFORMATTED' ) END IF if(neve.ge.1) then write(*,*) neve, elostt*1.d3 endif neve=neve+1 elostt=0 c WRITE (IODRAW) -NCASE, LSTACK, LSTMAX, SNGL (TKESUM), c & SNGL (WEIPRI) * +-------------------------------------------------------------------* * | Patch for heavy ions: it works only for 1 source particle on * | the stack for the time being IF ( ABS (ILO(LSTACK)) .GE. 10000 ) THEN IONID = ILO (LSTACK) CALL DCDION ( IONID ) c WRITE (IODRAW) ( IONID,SNGL(TKE(I)+AMNHEA(-IONID)),SNGL(WT(I)), c & SNGL (XA(I)), SNGL (YA(I)), SNGL (ZA(I)), c & SNGL (TX(I)), SNGL (TY(I)), SNGL (TZ(I)), c & I = 1, LSTACK ) * | * +-------------------------------------------------------------------* * | ELSE c WRITE (IODRAW) ( ILO(I), SNGL (TKE(I)+AM(ILO(I))), SNGL(WT(I)), c & SNGL (XA(I)), SNGL (YA(I)), SNGL (ZA(I)), c & SNGL (TX(I)), SNGL (TY(I)), SNGL (TZ(I)), c & I = 1, LSTACK ) END IF * | * +-------------------------------------------------------------------* RETURN * *======================================================================* * * * USer dependent DRAWing: * * * * Icode = 10x: call from Kaskad * * 100: elastic interaction secondaries * * 101: inelastic interaction secondaries * * 102: particle decay secondaries * * 103: delta ray generation secondaries * * 104: pair production secondaries * * 105: bremsstrahlung secondaries * * Icode = 20x: call from Emfsco * * 208: bremsstrahlung secondaries * * 210: Moller secondaries * * 212: Bhabha secondaries * * 214: in-flight annihilation secondaries * * 215: annihilation at rest secondaries * * 217: pair production secondaries * * 219: Compton scattering secondaries * * 221: photoelectric secondaries * * 225: Rayleigh scattering secondaries * * Icode = 30x: call from Kasneu * * 300: interaction secondaries * * Icode = 40x: call from Kashea * * 400: delta ray generation secondaries * * For all interactions secondaries are put on FINUC common (kp=1,np) * * but for KASHEA delta ray generation where only the secondary elec- * * tron is present and stacked on STACK common for kp=lstack * * * *======================================================================* * ENTRY USDRAW ( ICODE, MREG, XSCO, YSCO, ZSCO ) IF ( .NOT. LFCOPE ) THEN LFCOPE = .TRUE. IF ( KOMPUT .EQ. 2 ) THEN FILNAM = '/'//CFDRAW(1:8)//' DUMP A' ELSE FILNAM = CFDRAW END IF c OPEN ( UNIT = IODRAW, FILE = FILNAM, STATUS = 'NEW', FORM = c & 'UNFORMATTED' ) END IF RETURN *=== End of subrutine Mgdraw ==========================================* END