[fluka-discuss]: MGDRAW creates huge unwanted files

From: Charles Arrowsmith <charles.arrowsmith_at_physics.ox.ac.uk>
Date: Thu, 28 Oct 2021 16:35:59 +0000

Dear experts,

I am using the mgdraw.f subroutine to output files containing data of particles as they cross a chosen boundary (between regions referred to as "CAPW2" and "INNER" in the code).

When I run the simulation, an unwanted file is generated named 'MGDRAW' which is considerably larger than the useful collision tape files. This did not happen when I used the previous version of the mgdraw subroutine.

Can you see anything in my subroutine file (below) which is instructing this additional file to be generated? If not, how can I prevent its generation?

Many thanks,
Charles


*$ CREATE MGDRAW.FOR
*COPY MGDRAW
* *
*=== mgdraw ===========================================================*
* *
      SUBROUTINE MGDRAW ( ICODE, MREG )

      INCLUDE '(DBLPRC)'
      INCLUDE '(DIMPAR)'
      INCLUDE '(IOUNIT)'
*
*----------------------------------------------------------------------*
* *
* Copyright (C) 1990-2021 by Alfredo Ferrari & Paola Sala *
* All Rights Reserved. *
* *
* *
* MaGnetic field trajectory DRAWing: actually this entry manages *
* all trajectory dumping for *
* drawing *
* *
* Created on 01 March 1990 by Alfredo Ferrari *
* INFN - Milan *
* *
* Last change 03-Apr-21 by Alfredo Ferrari & Paola Sala *
* Private INFN - Milan *
* *
*----------------------------------------------------------------------*
*
      INCLUDE '(CASLIM)'
      INCLUDE '(COMPUT)'
      INCLUDE '(SOURCM)'
      INCLUDE '(FHEAVY)'
      INCLUDE '(FLKSTK)'
      INCLUDE '(GENSTK)'
      INCLUDE '(MGDDCM)'
      INCLUDE '(PAPROP)'
      INCLUDE '(QUEMGD)'
      INCLUDE '(SUMCOU)'
      INCLUDE '(TRACKR)'
*
      DIMENSION DTQUEN ( MXTRCK, MAXQMG ), AMHELP ( MFSTCK )
*
      CHARACTER*20 FILNAM
      CHARACTER*8 MRGNAM, NRGNAM
      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
         OPEN ( UNIT = IODRAW, FILE = FILNAM, STATUS = 'NEW', FORM =
     & 'UNFORMATTED' )
      END IF
      WRITE (IODRAW) NTRACK, MTRACK, JTRACK, SNGL (ETRACK),
     & SNGL (WTRACK)
      WRITE (IODRAW) ( SNGL (XTRACK (I)), SNGL (YTRACK (I)),
     & SNGL (ZTRACK (I)), I = 0, NTRACK ),
     & ( SNGL (DTRACK (I)), I = 1, MTRACK ),
     & SNGL (CTRACK)
* +-------------------------------------------------------------------*
* | Quenching is activated
      IF ( LQEMGD ) THEN
         IF ( MTRACK .GT. 0 ) THEN
            RULLL = ZERZER
            CALL QUENMG ( ICODE, MREG, RULLL, DTQUEN )
            WRITE (IODRAW) ( ( SNGL (DTQUEN (I,JBK)), I = 1, MTRACK ),
     & JBK = 1, NQEMGD )
         END IF
      END IF
* | End of quenching
* +-------------------------------------------------------------------*
      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 )
      IF ( .NOT. LFCOPE ) THEN
         LFCOPE = .TRUE.
         OPEN ( UNIT = 56, FILE = "collfile1_pi+", STATUS = 'UNKNOWN')
         OPEN ( UNIT = 57, FILE = "collfile1_pi-", STATUS = 'UNKNOWN')
      END IF
      CALL GEOR2N ( MREG, MRGNAM, IERR1 )
      CALL GEOR2N ( NEWREG, NRGNAM, IERR2 )
      IF(IERR1 .NE. 0 .OR. IERR2 .NE. 0) STOP "Error in name conversion"

      IF(MRGNAM .EQ. "CAPW2" .AND. NRGNAM .EQ. "INNER") THEN
         IF(JTRACK .EQ. 13) WRITE(56,'(1P,8G25.15)')
     & XSCO, YSCO, ZSCO, ETRACK, CXTRCK, CYTRCK, CZTRCK, WTRACK
         IF(JTRACK .EQ. 14) WRITE(57,'(1P,8G25.15)')
     & XSCO, YSCO, ZSCO, ETRACK, CXTRCK, CYTRCK, CZTRCK, WTRACK
      END IF

      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 *
* 16: recoil from (heavy) bremsstrahlung *
* 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 *
* 42: delta ray stack overflow *
* Icode = 5x: call from Kasoph *
* 50: optical photon absorption *
* 51: escape *
* 52: time kill *
* *
*======================================================================*
* *
      ENTRY ENDRAW ( ICODE, MREG, RULL, XSCO, YSCO, ZSCO )
      RETURN
*
*======================================================================*
* *
* SOurce particle DRAWing: *
* *
*======================================================================*
*
      ENTRY SODRAW
      RETURN
*
*======================================================================*
* *
* USer dependent DRAWing: *
* *
* Icode = 99: call from Doiosp, ion splitting secondaries *
* 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 *
* 106: de-excitation in flight secondaries *
* 110: radioactive decay products *
* 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 *
* 237: mu pair production 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 GENSTK common (kp=1,np) *
* but for KASHEA delta ray generation where only the secondary elec- *
* tron is present and stacked on FLKSTK common for kp=npflka *
* *
* !!! For optical photon production events, please refer to the !!! *
* !!! pshckp, ustckv (Cerenkov), pshscp, ustscn (Scintillation) !!! *
* !!! user routines !!! *
* *
*======================================================================*
*
      ENTRY USDRAW ( ICODE, MREG, XSCO, YSCO, ZSCO )
      RETURN
*=== End of subrutine Mgdraw ==========================================*
      END



__________________________________________________________________________
You can manage unsubscription from this mailing list at https://www.fluka.org/fluka.php?id=acc_info
Received on Thu Oct 28 2021 - 20:21:51 CEST

This archive was generated by hypermail 2.3.0 : Thu Oct 28 2021 - 20:22:02 CEST