(no subject)

From: Hantao Jing <jinght_at_mail.ihep.ac.cn>
Date: Mon, 08 Aug 2011 15:40:18 +0800

Gecko/20110616 Thunderbird/3.1.11
MIME-Version: 1.0
To: fluka-discuss_at_fluka.org
Subject: "STOP NO CHANNEL SELECTED" appears!
Content-Type: multipart/mixed;
 boundary="------------060208090203010109010204"
Sender: owner-fluka-discuss_at_mi.infn.it

This is a multi-part message in MIME format.
--------------060208090203010109010204
Content-Type: text/plain; charset=ISO-8859-1; format=flowed
Content-Transfer-Encoding: 7bit

Dear FLUKA experts,

          When I has submitted 128 jobs on server today, I find one of
my jobs aborts run and shows the following
errors:
  Abort called from ICLSSF reason NO CHANNEL SELECTED Run stopped!
  STOP NO CHANNEL SELECTED

       My fluka is the last version 2011.2.4 download this morning. How
to avoid these errors?
       Thank you very much!

                                                                 Hantao Jing
                                                                  2011-8-8

--------------060208090203010109010204
Content-Type: text/plain;
 name="mgdraw.f"
Content-Transfer-Encoding: 7bit
Content-Disposition: attachment;
 filename="mgdraw.f"

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

      INCLUDE '(DBLPRC)'
      INCLUDE '(DIMPAR)'
      INCLUDE '(IOUNIT)'
*
*----------------------------------------------------------------------*
* *
* Copyright (C) 1990-2006 by Alfredo Ferrari *
* 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 05-may-06 by Alfredo Ferrari *
* 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 )
*
      CHARACTER*20 FILNAM
      LOGICAL LFCOPE
      SAVE LFCOPE
      DATA LFCOPE / .FALSE. /
      COMMON/NUMBERIN/NUMSIZE
*
*----------------------------------------------------------------------*
* *
* 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 *
* *
*----------------------------------------------------------------------*

* | 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=60, FILE = 'Ang.60',FORM = 'FORMATTED',
     & STATUS = 'UNKNOWN')

      END IF

      IF( JTRACK.EQ.10) THEN ! Select muon+
        IF(ETRACK.GT.AM(JTRACK)) THEN ! Muon has survived
          TPPTRACK = ETRACK - AM(JTRACK)

* IF((TPPTRACK .GE. 3.9E-3) .AND. (TPPTRACK .GE. 4.1E-3)) THEN
* Calculate the x' and y' in phase diagram.
* NOTE: Now the beam direction is x axis for 90 degree detecter
* y and z is the horizotal and vertical directions respectively
*

************************ 0 degree ***************************
      IF(MREG.EQ.6 .AND. NEWREG.EQ.7) THEN ! 0 degree
* Solid angle (unit: sr) and x direction cosine
      srad = 0.8D0
      coszTH = 1.0D0 - srad/(2. * 3.1415926535897932384626433832795)
      cosn = CZTRCK
         IF(cosn .GE. coszTH) THEN

      IANG = 0
      xn = XSCO*10.
      yn = YSCO*10.

      PPx = CXTRCK * PTRACK
      PPy = CYTRCK * PTRACK
      PPz = CZTRCK * PTRACK

      XPP = 1000. * PPx / PPz
      YPP = 1000. * PPy / PPz

      WRITE(60,200)IANG, xn, XPP, yn, YPP, TPPTRACK, ATRACK
         END IF

************************ 15 degree ***************************
      ELSE IF(MREG.EQ.8 .AND. NEWREG.EQ.9) THEN ! 15 degree
      IANG = 15

* Rotate an angle (AngR) with repect to y axis
      AngR = 15.*3.1415926/180.

* Solid angle (unit: sr) and x direction cosine
      srad = 0.8D0
      coszTH = 1.0D0 - srad/(2. * 3.1415926535897932384626433832795)
      PPx = CXTRCK * PTRACK
      PPy = CYTRCK * PTRACK
      PPz = CZTRCK * PTRACK
      CALL ROTSYS(PPx,PPy,PPz,ANGR,Pxn,Pyn,Pzn)
* direction cosine in new coordinate system
      cosn = Pzn / PTRACK

         IF(cosn .GE. coszTH) THEN

      CALL ROTSYS(XSCO,YSCO,ZSCO,ANGR,xn,yn,zn)

      xn = xn*10.
      yn = yn*10.

      XPP = 1000. * Pxn / Pzn
      YPP = 1000. * pyn / Pzn

      WRITE(60,200)IANG, xn, XPP, yn, YPP, TPPTRACK, ATRACK

          END IF

************************ 30 degree ***************************
      ELSE IF(MREG.EQ.10 .AND. NEWREG.EQ.11) THEN ! 30 degree
      IANG = 30

* Rotate an angle (AngR) with repect to y axis
      AngR = 30.*3.1415926/180.

* Solid angle (unit: sr) and x direction cosine
      srad = 0.8D0
      coszTH = 1.0D0 - srad/(2. * 3.1415926535897932384626433832795)
      PPx = CXTRCK * PTRACK
      PPy = CYTRCK * PTRACK
      PPz = CZTRCK * PTRACK
      CALL ROTSYS(PPx,PPy,PPz,ANGR,Pxn,Pyn,Pzn)
* direction cosine in new coordinate system
      cosn = Pzn / PTRACK

         IF(cosn .GE. coszTH) THEN

      CALL ROTSYS(XSCO,YSCO,ZSCO,ANGR,xn,yn,zn)
      xn = xn*10.
      yn = yn*10.

      XPP = 1000. * Pxn / Pzn
      YPP = 1000. * pyn / Pzn

      WRITE(60,200)IANG, xn, XPP, yn, YPP, TPPTRACK, ATRACK

          END IF

************************ 45 degree ***************************
      ELSE IF(MREG.EQ.12 .AND. NEWREG.EQ.13) THEN ! 45 degree
      IANG = 45

* Rotate an angle (AngR) with repect to y axis
      AngR = 45.*3.1415926/180.

* Solid angle (unit: sr) and x direction cosine
      srad = 0.8D0
      coszTH = 1.0D0 - srad/(2. * 3.1415926535897932384626433832795)
      PPx = CXTRCK * PTRACK
      PPy = CYTRCK * PTRACK
      PPz = CZTRCK * PTRACK
      CALL ROTSYS(PPx,PPy,PPz,ANGR,Pxn,Pyn,Pzn)
* direction cosine in new coordinate system
      cosn = Pzn / PTRACK

         IF(cosn .GE. coszTH) THEN

      CALL ROTSYS(XSCO,YSCO,ZSCO,ANGR,xn,yn,zn)
      xn = xn*10.
      yn = yn*10.

      XPP = 1000. * Pxn / Pzn
      YPP = 1000. * pyn / Pzn

      WRITE(60,200)IANG, xn, XPP, yn, YPP, TPPTRACK, ATRACK

         END IF

************************ 60 degree ***************************
      ELSE IF(MREG.EQ.14 .AND. NEWREG.EQ.15) THEN ! 60 degree
      IANG = 60

* Rotate an angle (AngR) with repect to y axis
      AngR = 60.*3.1415926/180.

* Solid angle (unit: sr) and x direction cosine
      srad = 0.8D0
      coszTH = 1.0D0 - srad/(2. * 3.1415926535897932384626433832795)
      PPx = CXTRCK * PTRACK
      PPy = CYTRCK * PTRACK
      PPz = CZTRCK * PTRACK
      CALL ROTSYS(PPx,PPy,PPz,ANGR,Pxn,Pyn,Pzn)
* direction cosine in new coordinate system
      cosn = Pzn / PTRACK

         IF(cosn .GE. coszTH) THEN

      CALL ROTSYS(XSCO,YSCO,ZSCO,ANGR,xn,yn,zn)
      xn = xn*10.
      yn = yn*10.

      XPP = 1000. * Pxn / Pzn
      YPP = 1000. * pyn / Pzn

      WRITE(60,200)IANG, xn, XPP, yn, YPP, TPPTRACK, ATRACK

          END IF

************************ 75 degree ***************************
      ELSE IF(MREG.EQ.16 .AND. NEWREG.EQ.17) THEN ! 75 degree
      IANG = 75

* Rotate an angle (AngR) with repect to y axis
      AngR = 75.*3.1415926/180.

* Solid angle (unit: sr) and x direction cosine
      srad = 0.8D0
      coszTH = 1.0D0 - srad/(2. * 3.1415926535897932384626433832795)
      PPx = CXTRCK * PTRACK
      PPy = CYTRCK * PTRACK
      PPz = CZTRCK * PTRACK
      CALL ROTSYS(PPx,PPy,PPz,ANGR,Pxn,Pyn,Pzn)
* direction cosine in new coordinate system
      cosn = Pzn / PTRACK

         IF(cosn .GE. coszTH) THEN
      CALL ROTSYS(XSCO,YSCO,ZSCO,ANGR,xn,yn,zn)
      xn = xn*10.
      yn = yn*10.

      XPP = 1000. * Pxn / Pzn
      YPP = 1000. * pyn / Pzn

      WRITE(60,200)IANG, xn, XPP, yn, YPP, TPPTRACK, ATRACK

          END IF

************************ 90 degree ***************************
      ELSE IF(MREG.EQ.18 .AND. NEWREG.EQ.19) THEN ! 90 degree
      IANG = 90

* Rotate an angle (AngR) with repect to y axis
      AngR = 90.*3.1415926/180.

* Solid angle (unit: sr) and x direction cosine
      srad = 0.8D0
      coszTH = 1.0D0 - srad/(2. * 3.1415926535897932384626433832795)
      PPx = CXTRCK * PTRACK
      PPy = CYTRCK * PTRACK
      PPz = CZTRCK * PTRACK
      CALL ROTSYS(PPx,PPy,PPz,ANGR,Pxn,Pyn,Pzn)
* direction cosine in new coordinate system
      cosn = Pzn / PTRACK

         IF(cosn .GE. coszTH) THEN

      CALL ROTSYS(XSCO,YSCO,ZSCO,ANGR,xn,yn,zn)
      xn = xn*10.
      yn = yn*10.

      XPP = 1000. * Pxn / Pzn
      YPP = 1000. * pyn / Pzn

      WRITE(60,200)IANG, xn, XPP, yn, YPP, TPPTRACK, ATRACK
           END IF

      END IF

        ENDIF
      ENDIF

  200 format(I4, 6(1x, E12.5))

      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 *
* 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 )

* | end quenching
* +-------------------------------------------------------------------*
      RETURN
*
*======================================================================*
* *
* SOurce particle DRAWing: *
* *
*======================================================================*
*
      ENTRY SODRAW

* |
* +-------------------------------------------------------------------*
      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 *
* 110: 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 *
* 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 *
* *
*======================================================================*
*
      ENTRY USDRAW ( ICODE, MREG, XSCO, YSCO, ZSCO )

      RETURN
*=== End of subrutine Mgdraw ==========================================*
      END

      SUBROUTINE ROTSYS(XO,YO,ZO,ANG,XN,YN,ZN)
*Rotating an angle around the y axis
        DOUBLE PRECISION XO,YO,ZO,ANG,XN,YN,ZN

      XN = XO * COS(Ang) - ZO * SIN(Ang)
        YN = YO
        ZN = ZO * COS(Ang) + XO * SIN(Ang)

        RETURN
        END

--------------060208090203010109010204
Content-Type: text/plain;
 name="muonAngR113.inp"
Content-Transfer-Encoding: 7bit
Content-Disposition: attachment;
 filename="muonAngR113.inp"

* E:\jht\MuonSite\Geometries\SimTargDet.dat
* Created: 30.4.2010
* At: 2:48:17
TITLE
MC-CAD Test
GLOBAL 1000.0 0.0 0.0 0.0 1.0 0.
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
BEAM -1.6 -3.0 -3.0 -1.PROTON
BEAMPOS 0.0 0.0 -25.0
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
SOURCE 1.35 1.35 1.8
SOURCE 2.3 2.3 1.7 3.1&
* x x' y y' cut-off
* x x' y y'
* For beam core, WHASOU(1), WHASOU(2),WHASOU(3),WHASOU(4) denote FWHM of
gaussian distribution of x, x', y, y' respectively
* WHASOU(5) is the cut-off of beam core
* For beam halo, WHASOU(7), WHASOU(8),WHASOU(9),WHASOU(10) denote FWHM of
gaussian distribution of x, x', y, y' respectively
* unit: cm, mrad, cm, and mrad
*
GEOBEGIN
    0 0 MC-CAD
* A10b
  PLA A10b 0.70711 0.00000 -0.70711 42.426 0.000
-42.430
* A11b
  PLA A11b 0.50000 0.00000 -0.86603 30.000 0.000
-51.962
* A12b
  PLA A12b 0.25882 0.00000 -0.96593 15.529 0.000
-57.956
* A13a
  XYP A13a -60.00
* A1b
  XYP A1b 60.00
* A2b
  PLA A2b 0.25882 0.00000 0.96593 15.530 0.000
57.956
* A3b
  PLA A3b 0.50000 0.00000 0.86603 30.000 0.000
51.962
* A4b
  PLA A4b 0.70711 0.00000 0.70711 42.430 0.000
42.426
* A5b
  PLA A5b 0.86603 0.00000 0.50000 51.962 0.000
30.000
* A6b
  PLA A6b 0.96593 0.00000 0.25882 57.956 0.000
15.529
* A7b
  YZP A7b 60.00
* A8b
  PLA A8b 0.96593 0.00000 -0.25882 57.956 0.000
-15.529
* A9b
  PLA A9b 0.86603 0.00000 -0.50000 51.962 0.000
-30.000
* BH1
  RPP BH1 -2500.00 2500.00 -2500.00 2500.00 -2500.00
2500.00
* CC1
  RCC CC1 0.00 0.00 55.00 0.00 0.00
100.00
                6.77
* CC10
  RCC CC10 38.89 0.00 -38.89 70.71 0.00
-70.71
                6.77
* CC11
  RCC CC11 27.50 0.00 -47.63 50.00 0.00
-86.60
                6.77
* CC12
  RCC CC12 14.24 0.00 -53.13 25.88 0.00
-96.59
                6.77
* CC13
  RCC CC13 0.00 0.00 -155.00 0.00 0.00
100.00
                6.77
* CC2
  RCC CC2 14.24 0.00 53.13 25.88 0.00
96.59
                6.77
* CC3
  RCC CC3 27.50 0.00 47.63 50.00 0.00
86.60
                6.77
* CC4
  RCC CC4 38.89 0.00 38.89 70.71 0.00
70.71
                6.77
* CC5
  RCC CC5 47.63 0.00 27.50 86.60 0.00
50.00
                6.77
* CC6
  RCC CC6 53.13 0.00 14.24 96.59 0.00
25.88
                6.77
* CC7
  RCC CC7 55.00 0.00 0.00 100.00 0.00
 0.00
                6.77
* CC8
  RCC CC8 53.13 0.00 -14.24 96.59 0.00
-25.88
                6.77
* CC9
  RCC CC9 47.63 0.00 -27.50 86.60 0.00
-50.00
                6.77
* P1
  XYP P1 -7.50
* P2
  XYP P2 7.50
* TA
  RPP TA -1.5 1.5 -7.50 7.50 -20.00
20.00
* VA1
  RPP VA1 -2000.00 2000.00 -2000.00 2000.00 -2000.00
2000.00
  END
* Reg # 1
* BH; assigned material: Blackhole; mat # (1)
BH 5 +BH1 -VA1
* Reg # 2
* VA; assigned material: Vacuum; mat # (2)
VA 5 +VA1 -TA -CC1 -CC2 -CC3 -CC4 -CC5 -CC6 -CC7
           -CC8 -CC9 -CC10 -CC11 -CC12 -CC13
* Reg # 3
* TA1; assigned material: Vacuum; mat # (2)
TA1 5 +TA +P1
* Reg # 4
* TA2; assigned material: Carbon; mat # (6)
TA2 5 +P2 +TA -P1
* Reg # 5
* DE1; assigned material: Vacuum; mat # (2)
DE1 5 +TA -P2
* Reg # 6
* CDI1; assigned material: Vacuum; mat # (2) 0 degree
CDI1 5 +CC1 +A1b
* Reg # 7
* CDO1; assigned material: Vacuum; mat # (2)
CDO1 5 +CC1 -A1b
* Reg # 8
* CDI2; assigned material: Vacuum; mat # (2) 15 degree
CDI2 5 +CC2 +A2b
* Reg # 9
* CDO2; assigned material: Vacuum; mat # (2)
CDO2 5 +CC2 -A2b
* Reg # 10
* CDI3; assigned material: Vacuum; mat # (2) 30 degree
CDI3 5 +CC3 +A3b
* Reg # 11
* CDO3; assigned material: Vacuum; mat # (2)
CDO3 5 +CC3 -A3b
* Reg # 12
* CDI4; assigned material: Vacuum; mat # (2) 45 degree
CDI4 5 +CC4 +A4b
* Reg # 13
* CDO4; assigned material: Vacuum; mat # (2)
CDO4 5 +CC4 -A4b
* Reg # 14
* CDI5; assigned material: Vacuum; mat # (2) 60 degree
CDI5 5 +CC5 +A5b
* Reg # 15
* CDO5; assigned material: Vacuum; mat # (2)
CDO5 5 +CC5 -A5b
* Reg # 16
* CDI6; assigned material: Vacuum; mat # (2) 75 degree
CDI6 5 +CC6 +A6b
* Reg # 17
* CDO6; assigned material: Vacuum; mat # (2)
CDO6 5 +CC6 -A6b
* Reg # 18
* CDI7; assigned material: Vacuum; mat # (2) 90 degree
CDI7 5 +CC7 +A7b
* Reg # 19
* CDO7; assigned material: Vacuum; mat # (2)
CDO7 5 +CC7 -A7b
* Reg # 20
* CDI8; assigned material: Vacuum; mat # (2) 105 degree
CDI8 5 +CC8 +A8b
* Reg # 21
* CDO8; assigned material: Vacuum; mat # (2)
CDO8 5 +CC8 -A8b
* Reg # 22
* CDI9; assigned material: Vacuum; mat # (2) 120 degree
CDI9 5 +CC9 +A9b
* Reg # 23
* CDO9; assigned material: Vacuum; mat # (2)
CDO9 5 +CC9 -A9b
* Reg # 24
* CDI10; assigned material: Vacuum; mat # (2) 135 degree
CDI10 5 +CC10 +A10b
* Reg # 25
* CDO10; assigned material: Vacuum; mat # (2)
CDO10 5 +CC10 -A10b
* Reg # 26
* CDI11; assigned material: Vacuum; mat # (2) 150 degree
CDI11 5 +CC11 +A11b
* Reg # 27
* CDO11; assigned material: Vacuum; mat # (2)
CDO11 5 +CC11 -A11b
* Reg # 28
* CDI12; assigned material: Vacuum; mat # (2) 165 degree
CDI12 5 +CC12 +A12b
* Reg # 29
* CDO12; assigned material: Vacuum; mat # (2)
CDO12 5 +CC12 -A12b
* Reg # 30
* CDI13; assigned material: Vacuum; mat # (2) 180 degree
CDI13 5 +CC13 -A13a
* Reg # 31
* CDO13; assigned material: Vacuum; mat # (2)
CDO13 5 +CC13 +A13a
  END
GEOEND
*
ASSIGNMAT BLCKHOLE BH
ASSIGNMAT VACUUM VA
ASSIGNMAT VACUUM TA1
ASSIGNMAT CARBON TA2
ASSIGNMAT VACUUM DE1
ASSIGNMAT VACUUM CDI1
ASSIGNMAT VACUUM CDO1
ASSIGNMAT VACUUM CDI2
ASSIGNMAT VACUUM CDO2
ASSIGNMAT VACUUM CDI3
ASSIGNMAT VACUUM CDO3
ASSIGNMAT VACUUM CDI4
ASSIGNMAT VACUUM CDO4
ASSIGNMAT VACUUM CDI5
ASSIGNMAT VACUUM CDO5
ASSIGNMAT VACUUM CDI6
ASSIGNMAT VACUUM CDO6
ASSIGNMAT VACUUM CDI7
ASSIGNMAT VACUUM CDO7
ASSIGNMAT VACUUM CDI8
ASSIGNMAT VACUUM CDO8
ASSIGNMAT VACUUM CDI9
ASSIGNMAT VACUUM CDO9
ASSIGNMAT VACUUM CDI10
ASSIGNMAT VACUUM CDO10
ASSIGNMAT VACUUM CDI11
ASSIGNMAT VACUUM CDO11
ASSIGNMAT VACUUM CDI12
ASSIGNMAT VACUUM CDO12
ASSIGNMAT VACUUM CDI13
ASSIGNMAT VACUUM CDO13
*
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
PHYSICS 2.0 0.0 0.0 13.0 14.0 1.DECAYS
PHYSICS 1.0 0.0 0.0 10.0 11.0 1.DECAYS
PART-THR -1.0E-9 13.0 14.0 1.0 0.0
PART-THR -1.0E-6 10.0 11.0 1.0 0.0
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
MUPHOTON 1.0 0.0 0.0 3.0 25.0 1.DECAYS
*LAM-BIAS 0.0 0.02 1.0 13.0 14.0 1.INEPRI
*LAM-BIAS 0.0 0.02 1.0 10.0 11.0 1.INEPRI
*
*...+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USERDUMP 100.0 0.0 3.0 0.0
*
**current from the target
*(4.15-3.56)/4.0 = 16.6%
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI7 CDO7 144.MUONs90
USRBDX 1.0 0.0 3.0 6.283185 0.0 1.0&
************************************************************************************
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI1 CDO1 144.MUONs0
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI2 CDO2 144.MUONs15
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI3 CDO3 144.MUONs30
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI4 CDO4 144.MUONs45
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI5 CDO5 144.MUONs60
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI6 CDO6 144.MUONs75
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI7 CDO7 144.MUONs90
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI8 CDO8
144.MUONs105
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI9 CDO9
144.MUONs120
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI10 CDO10
144.MUONs135
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI11 CDO11
144.MUONs150
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI12 CDO12
144.MUONs165
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI13 CDO13
144.MUONs180
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
*
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 TA2 DE1 9.MUONsf
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 TA2 VA 360.MUONsl
USRBDX 4.15E-3 3.56E-3 3.0 6.283185 0.0 1.0&
*
*
*
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
RANDOMIZ 1.0 23996138.
*
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
START 1.0E8
STOP

--------------060208090203010109010204
Content-Type: text/plain;
 name="muonAngR113001.err"
Content-Transfer-Encoding: 7bit
Content-Disposition: attachment;
 filename="muonAngR113001.err"

1NUMBER OF BEAM NUMBER OF BEAM APPROXIMATE NUMBER AVERAGE
TIME USED TIME LEFT (RESERVED NUMBER OF STARS
 PARTICLES HANDLED PARTICLES LEFT OF BEAM PARTICLES BY A
BEAM PARTICLE 10000.0 SECONDS CREATED
                                            THAT CAN STILL BE
             FOR PRINTOUT)
                                            HANDLED

 NEXT SEEDS: 0 0 0 0 0 0 1778A
EF 0 0
          1 99999999 99999999
0.0000000E+00 1.0000000E+30 0
 NEXT SEEDS: 200 0 0 0 0 0 1778A
EF 0 0
  *** Umfnst:amsq,np0,np,kpart -2.08166817E-17 0 1 7
  *** Umfnst:amsq,np0,np,kpart -1.73472348E-17 0 1 7
  *** Umfnst:amsq,np0,np,kpart -1.73472348E-18 0 1 7
  *** Frmbrk: we are dealing with a bag of 7 96.6485596
  identical nucleons, go on folks! ***
 COUSET, TXYZ: 0.999999999987146 -0.999931865356875
1.167324368853537E-02
 COUSET, TXYZ: 0.999999999987146 -0.294967761766076
0.955507205359019
  *** Umfnst:amsq,np0,np,kpart -6.9388939E-18 0 1 7
 COUSET, TXYZ: 0.999999999986668 -0.748132569642864
0.663549288457837
  *** Umfnst:amsq,np0,np,kpart -6.9388939E-18 0 1 7
 COUSET, TXYZ: 1.00000000001527 -0.960939665821809
0.276757942398788
 COUSET, TXYZ: 0.999999999986443 -0.271620002541612
0.962404579266008
 COUSET, TXYZ: 0.999999999986443 -0.504165152069894
0.863607259934299
 COUSET, TXYZ: 1.00000000001041 -0.119841103230257
0.992793085188139
 COUSET, TXYZ: 1.00000000001041 -0.283945341072676
0.958840468119672
 COUSET, TXYZ: 1.00000000001041 -0.125266349506264
0.992123148455979
  *** Umfnst:amsq,np0,np,kpart -3.46944695E-18 0 1 7
 COUSET, TXYZ: 0.999999999993897 -0.527249004164124
0.849710825867091
 COUSET, TXYZ: 1.00000000001166 0.983386129601175
0.181526086641379
 GEOFAR, TXYZ: 0.999999999999493
  0.266705132536129 -0.836384441159938 -0.478883533715088
    Nfrom, Nreg, X, Y, Z 21 4
  0.572414960959732 0.541329187676517 -4.28432940778109
 Jtrack, Etrack 14 0.139594924202324
  *** Umfnst:amsq,np0,np,kpart -5.20417043E-18 0 1 7
  *** Umfnst:amsq,np0,np,kpart -6.9388939E-18 0 1 7
 COUSET, TXYZ: 0.999999999989886 -0.559474950244167
0.828847259770495
  *** Umfnst:amsq,np0,np,kpart -8.67361738E-18 0 1 7
  *** Umfnst:amsq,np0,np,kpart -8.67361738E-18 0 1 7
  *** Umfnst:amsq,np0,np,kpart -2.60208521E-17 0 1 7
 COUSET, TXYZ: 1.00000000001732 2.622431122578515E-02
0.999656083628453
 COUSET, TXYZ: 1.00000000000589 9.169729993030773E-02
-0.995786927609151
 COUSET, TXYZ: 1.00000000000500 -0.936304489456421
-0.351189269531063
  *** Umfnst:amsq,np0,np,kpart -6.9388939E-18 0 1 7
 COUSET, TXYZ: 1.00000000000830 -0.529241588752297
0.848471178503746
 COUSET, TXYZ: 1.00000000000829 -0.450870450601642
0.892589399887127
    2000000 98000000 98000000
3.8159348E-04 1.0000000E+30 916096
 NEXT SEEDS: 85832D1 2 0 0 0 0 1778A
EF 0 0
 COUSET, TXYZ: 0.999999999952075 -0.225666432392817
0.974204630041989
 COUSET, TXYZ: 0.999999999952075 -0.169042437002462
0.985608773498095
 COUSET, TXYZ: 0.999999999952075 -0.167883734497766
0.985806802368108
 COUSET, TXYZ: 0.999999999985376 -0.871710974725868
0.490020383773195
  *** Umfnst:amsq,np0,np,kpart -1.73472348E-18 0 1 7
 COUSET, TXYZ: 1.00000000001115 -0.593758021424604
0.804643655301052
 COUSET, TXYZ: 0.999999999994178 -0.488731306833013
0.872434358395892
 COUSET, TXYZ: 0.999999999994877 0.975291958679831
-0.220919884402046
 COUSET, TXYZ: 1.00000000000506 0.903109273044167
-0.429410806747761
 COUSET, TXYZ: 1.00000000000638 -0.946081571668304
0.323928479393813
 COUSET, TXYZ: 1.00000000012262 0.697390498848255
0.716691350834806
 COUSET, TXYZ: 1.00000000012262 0.685875269033570
0.727719118598216
  *** Frmbrk: we are dealing with a bag of 7 63.6098061
  identical nucleons, go on folks! ***
  *** Umfnst:amsq,np0,np,kpart -1.73472348E-18 0 1 7
  *** Umfnst:amsq,np0,np,kpart -1.21430643E-17 0 1 7
 COUSET, TXYZ: 1.00000000004498 -0.291184300659336
-0.956666976089116
 GEOFAR, TXYZ: 1.00000000000055
 -0.176920189613630 -0.693224363355029 0.698669613307462
    Nfrom, Nreg, X, Y, Z 1001 4
  5.549142106064558E-02 -1.25188060890405 0.263394778291778
 Jtrack, Etrack 8 0.939845624656418
  *** Umfnst:amsq,np0,np,kpart -3.46944695E-18 0 1 7
 COUSET, TXYZ: 0.999999999993470 8.857164829093248E-02
0.996069808349780
 COUSET, TXYZ: 0.999999999993470 9.774862108755841E-02
0.995211136926442
 COUSET, TXYZ: 0.999999999993470 0.105672036337147
0.994401036163630
 COUSET, TXYZ: 0.999999999990642 -0.798798279647275
0.601598959784538
  *** Umfnst:amsq,np0,np,kpart -1.04083409E-17 0 1 7
 COUSET, TXYZ: 1.00000000009218 -7.330126400145502E-02
0.997309843970338
  *** Umfnst:amsq,np0,np,kpart -1.21430643E-17 0 1 7
 COUSET, TXYZ: 1.00000000002086 0.998817533190679
4.861620545254491E-02
  *** Frmbrk: we are dealing with a bag of 7 73.2082825
  identical nucleons, go on folks! ***
  *** Umfnst:amsq,np0,np,kpart -1.04083409E-17 0 1 7
  *** Umfnst:amsq,np0,np,kpart -3.46944695E-18 0 1 7
  *** Umfnst:amsq,np0,np,kpart -6.9388939E-18 0 1 7
  *** Frmbrk: we are dealing with a bag of 7 72.9672775
  identical nucleons, go on folks! ***
 GEOFAR, TXYZ: 1.00000000000095
 -7.511057880733532E-02 0.517426227170309 -0.852425070249238
    Nfrom, Nreg, X, Y, Z 21 4
 -0.799546500803127 -0.605455145270748 -4.37115589293085
 Jtrack, Etrack 14 0.139612924489903
 COUSET, TXYZ: 1.00000000001359 0.477260345316841
0.878761948889015
 COUSET, TXYZ: 1.00000000001359 0.472679204901328
0.881234571088208
    4000000 96000000 96000000
3.8149625E-04 1.0000000E+30 1831970
 NEXT SEEDS:10A5B96F 4 0 0 0 0 1778A
EF 0 0
  *** Umfnst:amsq,np0,np,kpart -1.73472348E-18 0 1 7
 COUSET, TXYZ: 1.00000000000565 -0.620368685200731
0.784310330439180
  *** Umfnst:amsq,np0,np,kpart -5.20417043E-18 0 1 7
 COUSET, TXYZ: 1.00000000000540 -0.710524361645849
-0.703672602506704
  *** Umfnst:amsq,np0,np,kpart -1.56125113E-17 0 1 7
  *** Umfnst:amsq,np0,np,kpart -3.46944695E-18 0 1 7
 COUSET, TXYZ: 1.00000000000541 0.981855316572431
-0.189631583153413
  *** Umfnst:amsq,np0,np,kpart -2.08166817E-17 0 1 7
 COUSET, TXYZ: 0.999999999987473 -0.423544578313518
0.905875261918643
  *** Umfnst:amsq,np0,np,kpart -6.9388939E-18 0 1 7
  *** Umfnst:amsq,np0,np,kpart -5.20417043E-18 0 1 7
  *** Umfnst:amsq,np0,np,kpart -2.42861287E-17 0 1 7
 COUSET, TXYZ: 1.00000000002359 0.251719546300582
-0.967800222182972
 COUSET, TXYZ: 1.00000000002359 0.118567461370023
0.992945999111457
 COUSET, TXYZ: 1.00000000003311 -3.719063853123050E-02
0.999308188934657
 COUSET, TXYZ: 1.00000000000558 -0.981634525708158
0.190771218869299
 COUSET, TXYZ: 1.00000000001167 0.519470088752745
0.854488634748622
 COUSET, TXYZ: 1.00000000001167 0.474783695973976
0.880102517926542
  *** Umfnst:amsq,np0,np,kpart -5.20417043E-18 0 1 7
 COUSET, TXYZ: 1.00000000000660 -0.447775011391053
0.894146262748409
  *** Umfnst:amsq,np0,np,kpart -1.21430643E-17 0 1 7
 GEOFAR, TXYZ: 1.00000000000091
 -0.264897320210584 0.944080906051403 0.196317733728324
    Nfrom, Nreg, X, Y, Z 1001 4
  0.782389651942299 -9.150608241397973E-02 4.78652130217523
 Jtrack, Etrack 8 0.939722443041278
  *** Frmbrk: we are dealing with a bag of 7 144.556625
  identical nucleons, go on folks! ***
  *** Umfnst:amsq,np0,np,kpart -3.46944695E-18 0 1 7
 COUSET, TXYZ: 0.999999999990908 0.723949708292262
0.689852752292376
  *** Umfnst:amsq,np0,np,kpart -1.90819582E-17 0 1 7
  *** Umfnst:amsq,np0,np,kpart -1.04083409E-17 0 1 7
 GEOFAR, TXYZ: 0.999999999995793
 -2.188093366832352E-02 0.197644301348067 0.980029568369252
    Nfrom, Nreg, X, Y, Z 61 4
  2.926201655108625E-02 1.65782926050091 5.05350369086335
 Jtrack, Etrack 1 0.938278905522041
 GEOFAR, TXYZ: 0.999999999999456
  0.950246533569690 -0.119019083430328 0.287864522331436
    Nfrom, Nreg, X, Y, Z 21 4
 -0.286763531678952 -0.155312280883193 -2.66171319841339
 Jtrack, Etrack 14 0.139610073721744
 COUSET, TXYZ: 0.999999999991506 0.951936293724240
-0.306296086611580
 COUSET, TXYZ: 0.999999999991506 0.948411497336591
0.317042003057604
 COUSET, TXYZ: 0.999999999991506 0.969212655057983
0.246225159678022
 COUSET, TXYZ: 1.00000000000571 0.207434153212954
0.978248982668652
 COUSET, TXYZ: 1.00000000009921 -0.286037403284620
0.958218453235280
 COUSET, TXYZ: 1.00000000009921 -0.244104701840270
0.969748882308143
 COUSET, TXYZ: 0.999999999976901 0.988224173958156
0.153013012383013
 COUSET, TXYZ: 0.999999999976901 0.980444276408484
0.196796902444240
 GEOFAR, TXYZ: 1.00000000000152
 -0.681430507153289 0.562889295584380 -0.467769285909604
    Nfrom, Nreg, X, Y, Z 21 4
 -7.947303203883899E-02 3.340846254769551E-02 2.89790335092199
 Jtrack, Etrack 14 0.139572484669863
 COUSET, TXYZ: 1.00000000000666 -0.996629417534488
8.203538333053807E-02
 COUSET, TXYZ: 1.00000000001105 0.455717743978030
0.890124338418895
 COUSET, TXYZ: 0.999999999993583 -0.171995631953506
0.985097712197160
 COUSET, TXYZ: 0.999999999993583 -0.171140551225180
0.985246624817110
 COUSET, TXYZ: 0.999999999993651 0.886561293188257
0.462611147085396
 COUSET, TXYZ: 0.999999999993650 0.880780625862165
-0.473524539061234
    6000000 94000000 94000000
3.8149532E-04 1.0000000E+30 2747505
 NEXT SEEDS:18EB4407 6 0 0 0 0 1778A
EF 0 0
 COUSET, TXYZ: 0.999999999992310 0.822295171087278
0.569061201973183
  *** Umfnst:amsq,np0,np,kpart -1.21430643E-17 0 1 7
 COUSET, TXYZ: 1.00000000003688 -0.859512581237928
0.511114588685820
  *** Umfnst:amsq,np0,np,kpart -1.38777878E-17 0 1 7
 COUSET, TXYZ: 0.999999999935906 -0.638276116158333
0.769807508026290
 COUSET, TXYZ: 0.999999999951755 0.822197967929616
-0.569201635131102
  *** Umfnst:amsq,np0,np,kpart -3.46944695E-18 0 1 7
  *** Frmbrk: we are dealing with a bag of 7 82.6904068
  identical nucleons, go on folks! ***
  *** Umfnst:amsq,np0,np,kpart -1.38777878E-17 0 1 7
 COUSET, TXYZ: 0.999999999975664 7.808359672133185E-02
0.996946814967774
 COUSET, TXYZ: 0.999999999975664 7.965300914869076E-02
0.996822651269967
 COUSET, TXYZ: 0.999999999992801 0.999928914233526
1.192335797346372E-02
 COUSET, TXYZ: 0.999999999993446 -0.452252672314205
0.891889858879196
  *** Umfnst:amsq,np0,np,kpart -5.20417043E-18 0 1 7
 COUSET, TXYZ: 0.999999999990941 -0.236818671723168
0.971553867114508
    8000000 92000000 92000000
3.8149075E-04 1.0000000E+30 3663719
 NEXT SEEDS:213B7738 8 0 0 0 0 1778A
EF 0 0
 COUSET, TXYZ: 0.999999999991029 0.943352305090669
0.331792749261010
 COUSET, TXYZ: 0.999999999993813 0.949070402084399
-0.315064075824240
  *** Umfnst:amsq,np0,np,kpart -3.46944695E-18 0 1 7
  *** Umfnst:amsq,np0,np,kpart -1.56125113E-17 0 1 7
  *** Umfnst:amsq,np0,np,kpart -8.67361738E-18 0 1 7
 COUSET, TXYZ: 0.999999999993811 -0.773470716401495
-0.633832036786546
  *** Umfnst:amsq,np0,np,kpart -6.9388939E-18 0 1 7
 GEOFAR, TXYZ: 0.999999999999139
 -0.789121249673125 -0.269138288144438 0.552134254658490
    Nfrom, Nreg, X, Y, Z 21 4
  0.874055963043394 0.726676623810833 1.33472532046060
 Jtrack, Etrack 14 0.139598141866047
 COUSET, TXYZ: 1.00000000001045 -0.475244249408089
0.879853910274562
 COUSET, TXYZ: 1.00000000001201 -0.347041044969507
-0.937849941691367
 COUSET, TXYZ: 1.00000000000830 -0.100037589259283
0.994983658535050
 COUSET, TXYZ: 0.999999999991449 -0.474933549561659
0.880021660803676
 COUSET, TXYZ: 0.999999999990446 -0.426129553487627
0.904662148885057
 COUSET, TXYZ: 0.999999999990447 -0.596897026765200
0.802317854356836
 COUSET, TXYZ: 0.999999999990446 -0.427765443087761
0.903889775183249
  *** Umfnst:amsq,np0,np,kpart -6.9388939E-18 0 1 7
  *** Umfnst:amsq,np0,np,kpart -2.08166817E-17 0 1 7
 COUSET, TXYZ: 0.999999999957471 6.698507884592352E-02
0.997753977254386
 COUSET, TXYZ: 0.999999999957470 6.454077904412871E-02
0.997915070411965
 COUSET, TXYZ: 0.999999999985030 0.807076429090004
0.590446981173913
 COUSET, TXYZ: 0.999999999985030 0.936087411648327
0.351767476784874
 GEOFAR, TXYZ: 0.999999999991514
  0.807082503169162 -0.224089059518150 -0.546261774669891
    Nfrom, Nreg, X, Y, Z 21 4
 -0.547458450433972 -0.510599790394986 -0.523866198001528
 Jtrack, Etrack 14 0.139574477534302
  *** Umfnst:amsq,np0,np,kpart -6.9388939E-18 0 1 7
  *** Frmbrk: we are dealing with a bag of 7 39.6735344
  identical nucleons, go on folks! ***
 GEOFAR, TXYZ: 1.00000000000196
  0.558088309381928 -0.780697515522810 -0.281156234488311
    Nfrom, Nreg, X, Y, Z 1001 4
 -8.639186483329980E-02 4.82303685476141 4.34788758214788
 Jtrack, Etrack 8 0.939646967115010
 COUSET, TXYZ: 0.999999999941838 0.500530831744293
0.865718710873828
 COUSET, TXYZ: 0.999999999941838 0.506531434198102
0.862221494775496
 COUSET, TXYZ: 0.999999999993928 0.898529993903140
-0.438912121095190
  *** Umfnst:amsq,np0,np,kpart -6.9388939E-18 0 1 7
  *** Umfnst:amsq,np0,np,kpart -3.46944695E-18 0 1 7
  *** Frmbrk: we are dealing with a bag of 7 44.9836006
  identical nucleons, go on folks! ***
  *** Umfnst:amsq,np0,np,kpart -6.9388939E-18 0 1 7
  *** Frmbrk: we are dealing with a bag of 7 31.9405842
  identical nucleons, go on folks! ***
  *** Umfnst:amsq,np0,np,kpart -1.56125113E-17 0 1 7
   10000000 90000000 90000000
3.8153850E-04 1.0000000E+30 4581013
 NEXT SEEDS:29AB1E15 A 0 0 0 0 1778A
EF 0 0
 COUSET, TXYZ: 0.999999999994878 0.190609118926602
0.981666014371374
 COUSET, TXYZ: 1.00000000001254 0.994652081005271
-0.103282320737693
 COUSET, TXYZ: 1.00000000003798 -0.993063693555821
0.117577636552341
  *** Umfnst:amsq,np0,np,kpart -1.73472348E-18 0 1 7
 COUSET, TXYZ: 0.999999999981237 0.895438619582586
0.445184993595367
 COUSET, TXYZ: 1.00000000000600 0.667230293706209
0.744851485312828
 GEOFAR, TXYZ: 1.00000000000116
  2.622213102226862E-02 1.355108090943295E-02 0.999564289104588
    Nfrom, Nreg, X, Y, Z 1001 4
 -0.286654398072113 0.351000916566526 1.83202746619279
 Jtrack, Etrack 8 0.939568484078557
  *** Umfnst:amsq,np0,np,kpart -1.04083409E-17 0 1 7
 COUSET, TXYZ: 0.999999999932121 0.900650030606747
0.434545190092247
 COUSET, TXYZ: 0.999999999932121 0.883962239817828
0.467558294162868
  *** Umfnst:amsq,np0,np,kpart -1.21430643E-17 0 1 7
  *** Frmbrk: we are dealing with a bag of 8 150.789124
  identical nucleons, go on folks! ***
  *** Umfnst:amsq,np0,np,kpart -5.20417043E-18 0 1 7
  *** Umfnst:amsq,np0,np,kpart -3.46944695E-18 0 1 7
  *** Frmbrk: we are dealing with a bag of 7 103.434158
  identical nucleons, go on folks! ***
 COUSET, TXYZ: 0.999999999993495 -0.851104107486355
-0.524996950664330
 COUSET, TXYZ: 0.999999999987753 -0.827779670357058
-0.561053310585604
  *** Umfnst:amsq,np0,np,kpart -1.04083409E-17 0 1 7
  *** Umfnst:amsq,np0,np,kpart -8.67361738E-18 0 1 7
 COUSET, TXYZ: 1.00000000001047 0.295133646019463
0.955455980675295
  *** Umfnst:amsq,np0,np,kpart -5.20417043E-18 0 1 7
 GEOFAR, TXYZ: 1.00000000000130
 -0.284505152087590 0.354396716570996 0.890763596989632
    Nfrom, Nreg, X, Y, Z 1001 4
  -1.40184291906215 3.04722650417748 1.09826642799768
 Jtrack, Etrack 8 0.939653943597368
  *** Umfnst:amsq,np0,np,kpart -2.25514052E-17 0 1 7
  *** Umfnst:amsq,np0,np,kpart -1.21430643E-17 0 1 7
 COUSET, TXYZ: 1.00000000000550 5.419220565378591E-02
0.998530522746993
   12000000 88000000 88000000
3.8151949E-04 1.0000000E+30 5496886
 NEXT SEEDS:31E48088 C 0 0 0 0 1778A
EF 0 0
 COUSET, TXYZ: 1.00000000001865 0.852573556490558
0.522607243358097
  *** Umfnst:amsq,np0,np,kpart -1.38777878E-17 0 1 7
 GEOFAR, TXYZ: 1.00000000000056
  0.392502881211748 -0.616934147843405 0.682153755004195
    Nfrom, Nreg, X, Y, Z 1001 4
  -1.00908542760971 0.699228520592620 0.790747307489254
 Jtrack, Etrack 8 0.939869312470807
 GEOFAR, TXYZ: 1.00000000000057
 -0.481153881984163 0.815784396244679 0.320915503982605
    Nfrom, Nreg, X, Y, Z 1001 4
   1.29651834955251 4.781151696522834E-02 5.51274637801259
 Jtrack, Etrack 8 0.939773705038167
 COUSET, TXYZ: 0.999999999993718 -0.734732149698490
0.678357330753397
 COUSET, TXYZ: 0.999999999992164 -0.999943041732915
1.067301617411206E-02
 COUSET, TXYZ: 0.999999999992164 -0.968126255987124
0.250462676765783
  *** Umfnst:amsq,np0,np,kpart -6.9388939E-18 0 1 7
 COUSET, TXYZ: 1.00000000000948 0.169723194914359
-0.985491774256403
 COUSET, TXYZ: 1.00000000000948 0.139716097047487
0.990191603804429
 GEOFAR, TXYZ: 1.00000000000052
  0.717244810090194 4.093485572671777E-02 0.695617869225881
    Nfrom, Nreg, X, Y, Z 1001 4
   1.34594922371369 -6.066194965723873E-02 4.43399666617644
 Jtrack, Etrack 8 0.939896902226253
 COUSET, TXYZ: 1.00000000000861 -0.196770406277004
0.980449594436552
 GEOFAR, TXYZ: 0.999999999999433
  0.931634307041118 0.217893652768462 0.290826192125295
    Nfrom, Nreg, X, Y, Z 3 4
  0.548618518311881 -1.04797164596745 1.21031043220856
 Jtrack, Etrack 23 0.134994928513118
  *** Umfnst:amsq,np0,np,kpart -8.67361738E-18 0 1 7
 COUSET, TXYZ: 1.00000000001501 -0.313137398834089
0.949707833747533
  *** Umfnst:amsq,np0,np,kpart -1.73472348E-18 0 1 7
 COUSET, TXYZ: 1.00000000003288 -0.653104720207573
0.757267604290810
  *** Umfnst:amsq,np0,np,kpart -1.73472348E-18 0 1 7
 COUSET, TXYZ: 0.999999999987880 -0.489168580988182
0.872189256612215
  *** Umfnst:amsq,np0,np,kpart -3.46944695E-18 0 1 7
 Abort called from ICLSSF reason NO CHANNEL SELECTED Run stopped!
 STOP NO CHANNEL SELECTED

--------------060208090203010109010204
Content-Type: text/plain;
 name="muonAngR113001.out"
Content-Transfer-Encoding: 8bit
Content-Disposition: attachment;
 filename="muonAngR113001.out"

1 *====================================================================*
  * *
  * *
  * *
  * *
  * FFFFF L U U K K AAA 222 000 11 11 *
  * F L U U K K A A 2 2 0 0 111 111 *
  * F L U U K K A A 2 0 0 1111 1111 *
  * FFFF L U U KK AAAAA == 2 0 0 11 11 *
  * F L U U K K A A 2 0 0 11 11 *
  * F L U U K K A A 2 0 0 11 11 *
  * F LLLLL UUU K K A A 22222 000 11111 11111 *
  * *
  * *
  * *
  * Version of Fluka2011 for GNU/Linux operating system *
  * *
  * By : *
  * *
  * Alfredo Ferrari & Paola Sala INFN Milan & CERN/EN *
  * *
  * Alfredo.Ferrari_at_cern.ch Paola.Sala_at_mi.infn.it *
  * *
  * *
  * Alberto Fasso` Jefferson Lab, Newport News *
  * *
  * afasso_at_jlab.org *
  * *
  * *
  * Johannes Ranft Siegen University *
  * *
  * Johannes.Ranft_at_cern.ch *
  * *
  * *
  * *
  * This version includes all the features of the Fluka2011 *
  * *
  * package *
  * *
  * *
  * *
  *====================================================================*

                     FLUKA User license

           COPYRIGHT NOTICE AND LICENSE CONDITIONS

  Copyright Italian National Institute for Nuclear Physics
  (INFN) and European Organization for Nuclear Research (CERN),
  1989-2011. All rights not expressly granted under this
  license are reserved. Requests for permissions not granted
  under this license shall be addressed to the FLUKA Collabora-
  tion Committee, through fcc_at_fluka.org. Any permission may
  only be granted in writing. This software results in
  particular from work performed by Alberto Fassò, Alfredo
  Ferrari, Johannes Ranft, Paola Sala (the "Authors"), and
  their collaborators (the "Collaborators"). INFN and CERN are
  the exclusive source of distribution of the code, bug fixes
  and documentation of the FLUKA software (FLUKA website), and
  may authorise distribution by mirror sites. This license
  cancels and replaces any prior license conditions but their
  warranty and liability provisions shall continue to apply to
  any use or modifications made under such prior license
  conditions.

  DEFINITIONS

  The FLUKA software ("FLUKA") means the fully integrated
  particle physics Monte Carlo simulation software package
  being developed since 1989, available from the official FLUKA
  website (http://www.fluka.org) and authorised mirror sites.
  FLUKA is made up of FLUKA core code and FLUKA User Routines.

  The FLUKA Copyright Holders means both CERN and INFN.

  FLUKA User Routines means the set of subroutines collected in
  the usermvax section of FLUKA and forming part of the
  standard distribution of FLUKA.

  The Licensee means any person acting individually within a
  non-profit organisation, exercising any permission granted by
  this license.

  LICENSE GRANT

  1.
  Subject to the terms and conditions of this license, the
  FLUKA Copyright Holders herewith grant to the Licensee a
  worldwide, non-exclusive, royalty-free, source and object
  code license to use and reproduce FLUKA for internal
  scientific non commercial non-military purposes only.
  Notwithstanding the foregoing, the Licensee shall not execute
  FLUKA in a manner that produces an output whose contents are
  directly useable or easily employable to simulate the physics
  models embedded within FLUKA in a generic manner, or excise
  portions of FLUKA source or object code, and execute them
  independently of FLUKA. Extracting specific isolated results
  from any of the individual internal physics models embedded
  within FLUKA is not permitted. Permitted use and reproduction
  are referred to below as "Use".

  2.
  Modification (including translation) of FLUKA, in whole or
  in part, is not permitted, except for modification of FLUKA
  User Routines that do not circumvent, replace, add to or
  modify any of the functions of the FLUKA core code. Permitted
  modifications are referred to below as "Modifications".

  3.
  FLUKA is licensed for Use by the Licensee only, and the
  Licensee shall not market, distribute, transfer, license or
  sub-license, or in any way make available ("Make Available")
  FLUKA or Modifications, in whole or in part, to third
  parties, without prior written permission. The Licensee shall
  not assign or transfer this license.

  4.
  Notwithstanding section 3, the Licensee may Make Available
  his Modifications of FLUKA User Routines to third parties
  under these license conditions.

  5.
  The Licensee shall not insert FLUKA code or Modifications,
  in whole or in part, into other codes without prior written
  permission.

  6.
  Any use of FLUKA outside the scope of this license is subject
  to prior written permission.

  GRANT BACK

  7.
  The Licensee shall in a timely fashion notify to
  fcc_at_fluka.org any Modifications carried out by him. Except
  for Authors, Collaborators, and employees of the FLUKA
  Copyright Holders, the copyright in whose Modifications shall
  automatically be vested in the FLUKA Copyright Holders, the
  Licensee herewith grants the FLUKA Copyright Holders a
  perpetual, royalty- free, irrevocable and non-exclusive
  license to his Modifications, with no limitation of use. The
  Licensee acknowledges that the FLUKA Copyright Holders may
  insert such Modifications into future releases of FLUKA,
  subject to appropriate acknowledgment of the Licensee's
  contribution.

  8.
  The Licensee shall report as soon as practical any errors or
  bugs found in any portion of FLUKA to fluka-discuss_at_fluka.org

  PUBLICATIONS AND ACKNOWLEDGEMENT

  9.
  The Licensee shall explicitly acknowledge his use of FLUKA in
  any publication or communication, scientific or otherwise,
  relating to such use, by citing the FLUKA set of references
  (http://www.fluka.org, see below) and the FLUKA copyright
  notice.

  10.
  The Licensee shall ensure that the FLUKA set of references,
  the FLUKA copyright notice and these license conditions are
  not altered or removed from FLUKA and that all embodiments of
  FLUKA and Modifications contain in full the FLUKA set of
  references, the FLUKA copyright notice, and these license
  conditions.

  11.
  Any insertion of FLUKA code or Modifications, in whole or in
  part, into other codes with permission under section 5 shall
  preserve the FLUKA set of references, the FLUKA copyright
  notice and these license conditions in the FLUKA code or
  Modifications concerned, and must also reproduce these within
  any additional global notices included along or embedded
  within the software into which the FLUKA code or the
  Modifications have been integrated, in whole or in part. Any
  part of the FLUKA code or Modifications so inserted shall
  continue to be subject to these license conditions.

  12.
  Publication of any results of comparisons of specific
  internal physics models extracted from FLUKA with permission
  under section 6 with data or with other codes or models is
  subject to prior written permission.

  13.
  Contributions to any formal code comparisons and validation
  exercises pertaining to FLUKA, sponsored by recognised bodies
  or within the framework of recognised conferences and
  workshops, are subject to prior written permission.

  WARRANTY AND LIABILITY

  14.
  DISCLAIMER FLUKA IS PROVIDED BY THE FLUKA COPYRIGHT HOLDERS
  "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT
  NOT LIMITED TO, IMPLIED WARRANTIES OF MERCHANTABILITY, OF
  SATISFACTORY QUALITY, AND FITNESS FOR A PARTICULAR PURPOSE OR
  USE ARE DISCLAIMED. THE FLUKA COPYRIGHT HOLDERS AND THE
  AUTHORS MAKE NO REPRESENTATION THAT FLUKA AND MODIFICATIONS
  THEREOF WILL NOT INFRINGE ANY PATENT, COPYRIGHT, TRADE SECRET
  OR OTHER PROPRIETARY RIGHT.

  15.
  LIMITATION OF LIABILITY THE FLUKA COPYRIGHT HOLDERS AND ANY
  CONTRIBUTOR SHALL HAVE NO LIABILITY FOR DIRECT, INDIRECT,
  SPECIAL, INCIDENTAL, CONSEQUENTIAL, EXEMPLARY, PUNITIVE OR
  OTHER DAMAGES OF ANY CHARACTER INCLUDING, WITHOUT LIMITATION,
  PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES, LOSS OF USE,
  DATA OR PROFITS, OR BUSINESS INTERRUPTION, HOWEVER CAUSED AND
  ON ANY THEORY OF CONTRACT, WARRANTY, TORT (INCLUDING
  NEGLIGENCE), PRODUCT LIABILITY OR OTHERWISE, ARISING IN ANY
  WAY OUT OF THE USE OF FLUKA, EVEN IF ADVISED OF THE
  POSSIBILITY OF SUCH DAMAGES, AND THE LICENSEE SHALL HOLD THE
  COPYRIGHT HOLDERS AND ANY CONTRIBUTOR FREE AND HARMLESS FROM
  ANY LIABILITY, INCLUDING CLAIMS BY THIRD PARTIES, IN RELATION
  TO SUCH USE.

  TERMINATION

  16.
  This license shall terminate with immediate effect and
  without notice if the Licensee fails to comply with any of
  the terms of this license, or if the Licensee initiates
  litigation against any of the FLUKA Copyright Holders or any
  contributors with regard to FLUKA. It shall also terminate
  with immediate effect from the date on which a new version of
  FLUKA becomes available. In either case sections 14 and 15
  above shall continue to apply to any Use or Modifications
  made under these license conditions.

    FLUKA set of references, subject to change

  "The FLUKA code: Description and benchmarking"
  G. Battistoni, S. Muraro, P.R. Sala, F. Cerutti, A. Ferrari,
  S. Roesler, A. Fasso`, J. Ranft,
  Proceedings of the Hadronic Shower Simulation Workshop 2006,
  Fermilab 6--8 September 2006, M.Albrow, R. Raja eds.,
  AIP Conference Proceeding 896, 31-49, (2007)

  "FLUKA: a multi-particle transport code"
  A. Fasso`, A. Ferrari, J. Ranft, and P.R. Sala,
  CERN-2005-10 (2005), INFN/TC_05/11, SLAC-R-773

  Additional FLUKA references can be added, provided they are
  relevant for the FLUKA version under consideration.

     !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     !!!! DOWNLOAD/USE OF THE FLUKA SOFTWARE IMPLIES FULL !!!!
     !!!! ACCEPTANCE AND COMPLIANCE WITH THE LICENSE !!!!
     !!!! CONDITIONS !!!!
     !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

   Note: The Nuclear Energy Agency Data Bank is an authorized
          distributor of the code

1
****************************************************************************************************

   FLUKA2011 Version 2.4 Jun-11 by A. Ferrari DATE: 8/ 8/11 TIME: 10:
9:51

     ****************************************************************************************************

 *---------------- E:\jht\MuonSite\Geometries\SimTargDet.dat
                            ----------------*
 *---------------- Created: 30.4.2010
                            ----------------*
 *---------------- At: 2:48:17
                            ----------------*

 ***** Next control card ***** TITLE 0.000 0.000 0.000
     0.000 0.000 0.000

     MC-CAD Test

 ***** Next control card ***** GLOBAL 1000. 0.000 0.000
     0.000 1.000 0.000

 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *---------------- x x' y y'
cut-off ----------------*
 *---------------- x x' y y'
                            ----------------*
 *---------------- For beam core, WHASOU(1),
WHASOU(2),WHASOU(3),WHASOU(4) denote FWHM of gaussia ----------------*
 *---------------- WHASOU(5) is the cut-off of beam core
                            ----------------*
 *---------------- For beam halo, WHASOU(7),
WHASOU(8),WHASOU(9),WHASOU(10) denote FWHM of gaussi ----------------*
 *---------------- unit: cm, mrad, cm, and mrad
                            ----------------*
 *----------------
                            ----------------*
 *----------------
                            ----------------*
 *----------------
                            ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *---------------- LAM-BIAS 0.0 0.02 1.0 13.0
  14.0 1.INEPRI ----------------*
 *---------------- LAM-BIAS 0.0 0.02 1.0 10.0
  11.0 1.INEPRI ----------------*
 *----------------
                            ----------------*
 *----------------
...+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
                            ----------------*
 *---------------- *current from the target
                            ----------------*
 *---------------- (4.15-3.56)/4.0 = 16.6%
                            ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
*******************************************************************************
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
                            ----------------*
 *----------------
                            ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
                            ----------------*
 *----------------
                            ----------------*
 *----------------
                            ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*
 *----------------
..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
  ----------------*

 ***** Next control card ***** BEAM -1.600 0.000 0.000
    -3.000 -3.000 -1.000 PROTON

 **** Density scaling factors start at location 1 and end at
4000 (I*4 addr.) ****

 ***** Next control card ***** BEAMPOS 0.000 0.000 -25.00
     0.000 0.000 0.000

 ***** Next control card ***** GEOBEGIN 0.000 0.000 0.000
     0.000 0.000 0.000

1

          MC-CAD

                    IVLFLG= 0 IDBG = 0

                                                  Body data
 *
 *--------------- A10b
                           ---------------*
 *
 *
 *--------------- A11b
                           ---------------*
 *
  PLA A10b 1 0.70711000E+00 0.00000000E+00 -0.70711000E+00
0.42426000E+02 0.00000000E+00 -0.42430000E+02 5
 *
 *--------------- A12b
                           ---------------*
 *
  PLA A11b 2 0.50000000E+00 0.00000000E+00 -0.86603000E+00
0.30000000E+02 0.00000000E+00 -0.51962000E+02 15
 *
 *--------------- A13a
                           ---------------*
 *
  PLA A12b 3 0.25882000E+00 0.00000000E+00 -0.96593000E+00
0.15529000E+02 0.00000000E+00 -0.57956000E+02 25
 *
 *--------------- A1b
                           ---------------*
 *
  XYP A13a 4 -0.60000000E+02 0.00000000E+00 0.00000000E+00
0.00000000E+00 0.00000000E+00 0.00000000E+00 35
 *
 *--------------- A2b
                           ---------------*
 *
  XYP A1b 5 0.60000000E+02 0.00000000E+00 0.00000000E+00
0.00000000E+00 0.00000000E+00 0.00000000E+00 45
 *
 *--------------- A3b
                           ---------------*
 *
  PLA A2b 6 0.25882000E+00 0.00000000E+00 0.96593000E+00
0.15530000E+02 0.00000000E+00 0.57956000E+02 55
 *
 *--------------- A4b
                           ---------------*
 *
  PLA A3b 7 0.50000000E+00 0.00000000E+00 0.86603000E+00
0.30000000E+02 0.00000000E+00 0.51962000E+02 65
 *
 *--------------- A5b
                           ---------------*
 *
  PLA A4b 8 0.70711000E+00 0.00000000E+00 0.70711000E+00
0.42430000E+02 0.00000000E+00 0.42426000E+02 75
 *
 *--------------- A6b
                           ---------------*
 *
  PLA A5b 9 0.86603000E+00 0.00000000E+00 0.50000000E+00
0.51962000E+02 0.00000000E+00 0.30000000E+02 85
 *
 *--------------- A7b
                           ---------------*
 *
  PLA A6b 10 0.96593000E+00 0.00000000E+00 0.25882000E+00
0.57956000E+02 0.00000000E+00 0.15529000E+02 95
 *
 *--------------- A8b
                           ---------------*
 *
  YZP A7b 11 0.60000000E+02 0.00000000E+00 0.00000000E+00
0.00000000E+00 0.00000000E+00 0.00000000E+00 105
 *
 *--------------- A9b
                           ---------------*
 *
  PLA A8b 12 0.96593000E+00 0.00000000E+00 -0.25882000E+00
0.57956000E+02 0.00000000E+00 -0.15529000E+02 115
 *
 *--------------- BH1
                           ---------------*
 *
  PLA A9b 13 0.86603000E+00 0.00000000E+00 -0.50000000E+00
0.51962000E+02 0.00000000E+00 -0.30000000E+02 125
 *
 *--------------- CC1
                           ---------------*
 *
  RPP BH1 14 -0.25000000E+04 0.25000000E+04 -0.25000000E+04
0.25000000E+04 -0.25000000E+04 0.25000000E+04 135
 *
 *--------------- CC10
                           ---------------*
 *
  RCC CC1 15 0.00000000E+00 0.00000000E+00 0.55000000E+02
0.00000000E+00 0.00000000E+00 0.10000000E+03 145
                          0.67700000E+01
 *
 *--------------- CC11
                           ---------------*
 *
  RCC CC10 16 0.38890000E+02 0.00000000E+00 -0.38890000E+02
0.70710000E+02 0.00000000E+00 -0.70710000E+02 156
                          0.67700000E+01
 *
 *--------------- CC12
                           ---------------*
 *
  RCC CC11 17 0.27500000E+02 0.00000000E+00 -0.47630000E+02
0.50000000E+02 0.00000000E+00 -0.86600000E+02 167
                          0.67700000E+01
 *
 *--------------- CC13
                           ---------------*
 *
  RCC CC12 18 0.14240000E+02 0.00000000E+00 -0.53130000E+02
0.25880000E+02 0.00000000E+00 -0.96590000E+02 178
                          0.67700000E+01
 *
 *--------------- CC2
                           ---------------*
 *
  RCC CC13 19 0.00000000E+00 0.00000000E+00 -0.15500000E+03
0.00000000E+00 0.00000000E+00 0.10000000E+03 189
                          0.67700000E+01
 *
 *--------------- CC3
                           ---------------*
 *
  RCC CC2 20 0.14240000E+02 0.00000000E+00 0.53130000E+02
0.25880000E+02 0.00000000E+00 0.96590000E+02 200
                          0.67700000E+01
 *
 *--------------- CC4
                           ---------------*
 *
  RCC CC3 21 0.27500000E+02 0.00000000E+00 0.47630000E+02
0.50000000E+02 0.00000000E+00 0.86600000E+02 211
                          0.67700000E+01
 *
 *--------------- CC5
                           ---------------*
 *
  RCC CC4 22 0.38890000E+02 0.00000000E+00 0.38890000E+02
0.70710000E+02 0.00000000E+00 0.70710000E+02 222
                          0.67700000E+01
 *
 *--------------- CC6
                           ---------------*
 *
  RCC CC5 23 0.47630000E+02 0.00000000E+00 0.27500000E+02
0.86600000E+02 0.00000000E+00 0.50000000E+02 233
                          0.67700000E+01
 *
 *--------------- CC7
                           ---------------*
 *
  RCC CC6 24 0.53130000E+02 0.00000000E+00 0.14240000E+02
0.96590000E+02 0.00000000E+00 0.25880000E+02 244
                          0.67700000E+01
 *
 *--------------- CC8
                           ---------------*
 *
  RCC CC7 25 0.55000000E+02 0.00000000E+00 0.00000000E+00
0.10000000E+03 0.00000000E+00 0.00000000E+00 255
                          0.67700000E+01
 *
 *--------------- CC9
                           ---------------*
 *
  RCC CC8 26 0.53130000E+02 0.00000000E+00 -0.14240000E+02
0.96590000E+02 0.00000000E+00 -0.25880000E+02 266
                          0.67700000E+01
 *
 *--------------- P1
                           ---------------*
 *
  RCC CC9 27 0.47630000E+02 0.00000000E+00 -0.27500000E+02
0.86600000E+02 0.00000000E+00 -0.50000000E+02 277
                          0.67700000E+01
 *
 *--------------- P2
                           ---------------*
 *
  XYP P1 28 -0.75000000E+01 0.00000000E+00 0.00000000E+00
0.00000000E+00 0.00000000E+00 0.00000000E+00 288
 *
 *--------------- TA
                           ---------------*
 *
  XYP P2 29 0.75000000E+01 0.00000000E+00 0.00000000E+00
0.00000000E+00 0.00000000E+00 0.00000000E+00 298
 *
 *--------------- VA1
                           ---------------*
 *
  RPP TA 30 -0.15000000E+01 0.15000000E+01 -0.75000000E+01
0.75000000E+01 -0.20000000E+02 0.20000000E+02 308
  RPP VA1 31 -0.20000000E+04 0.20000000E+04 -0.20000000E+04
0.20000000E+04 -0.20000000E+04 0.20000000E+04 318
  END 32 0.00000000E+00 0.00000000E+00 0.00000000E+00
0.00000000E+00 0.00000000E+00 0.00000000E+00 328
 Number of bodies 31
 Length of FPD-Array 333

  Accuracy parameter: 1.00E-04 suggested: 1.00E-04

  Detected max. geometry dimension: 2.00E+03 cm

                                                  Input region data
 *
 *--------------- Reg # 1
                           ---------------*
 *
 *
 *--------------- BH; assigned material: Blackhole; mat # (1)
                           ---------------*
 *
BH 5 + BH1 - VA1
 *
 *--------------- Reg # 2
                           ---------------*
 *
 *
 *--------------- VA; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
VA 5 + VA1 - TA - CC1 -
CC2 - CC3 - CC4 - CC5 - CC6
- CC7 - CC8 - CC9 - CC10 -
CC11 - CC12 - CC13
 *
 *--------------- Reg # 3
                           ---------------*
 *
 *
 *--------------- TA1; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
TA1 5 + TA + P1
 *
 *--------------- Reg # 4
                           ---------------*
 *
 *
 *--------------- TA2; assigned material: Carbon; mat # (6)
                           ---------------*
 *
TA2 5 + P2 + TA - P1
 *
 *--------------- Reg # 5
                           ---------------*
 *
 *
 *--------------- DE1; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
DE1 5 + TA - P2
 *
 *--------------- Reg # 6
                           ---------------*
 *
 *
 *--------------- CDI1; assigned material: Vacuum; mat # (2) 0 degree
                           ---------------*
 *
CDI1 5 + CC1 + A1b
 *
 *--------------- Reg # 7
                           ---------------*
 *
 *
 *--------------- CDO1; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
CDO1 5 + CC1 - A1b
 *
 *--------------- Reg # 8
                           ---------------*
 *
 *
 *--------------- CDI2; assigned material: Vacuum; mat # (2) 15 degree
                           ---------------*
 *
CDI2 5 + CC2 + A2b
 *
 *--------------- Reg # 9
                           ---------------*
 *
 *
 *--------------- CDO2; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
CDO2 5 + CC2 - A2b
 *
 *--------------- Reg # 10
                           ---------------*
 *
 *
 *--------------- CDI3; assigned material: Vacuum; mat # (2) 30 degree
                           ---------------*
 *
CDI3 5 + CC3 + A3b
 *
 *--------------- Reg # 11
                           ---------------*
 *
 *
 *--------------- CDO3; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
CDO3 5 + CC3 - A3b
 *
 *--------------- Reg # 12
                           ---------------*
 *
 *
 *--------------- CDI4; assigned material: Vacuum; mat # (2) 45 degree
                           ---------------*
 *
CDI4 5 + CC4 + A4b
 *
 *--------------- Reg # 13
                           ---------------*
 *
 *
 *--------------- CDO4; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
CDO4 5 + CC4 - A4b
 *
 *--------------- Reg # 14
                           ---------------*
 *
 *
 *--------------- CDI5; assigned material: Vacuum; mat # (2) 60 degree
                           ---------------*
 *
CDI5 5 + CC5 + A5b
 *
 *--------------- Reg # 15
                           ---------------*
 *
 *
 *--------------- CDO5; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
CDO5 5 + CC5 - A5b
 *
 *--------------- Reg # 16
                           ---------------*
 *
 *
 *--------------- CDI6; assigned material: Vacuum; mat # (2) 75 degree
                           ---------------*
 *
CDI6 5 + CC6 + A6b
 *
 *--------------- Reg # 17
                           ---------------*
 *
 *
 *--------------- CDO6; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
CDO6 5 + CC6 - A6b
 *
 *--------------- Reg # 18
                           ---------------*
 *
 *
 *--------------- CDI7; assigned material: Vacuum; mat # (2) 90 degree
                           ---------------*
 *
CDI7 5 + CC7 + A7b
 *
 *--------------- Reg # 19
                           ---------------*
 *
 *
 *--------------- CDO7; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
CDO7 5 + CC7 - A7b
 *
 *--------------- Reg # 20
                           ---------------*
 *
 *
 *--------------- CDI8; assigned material: Vacuum; mat # (2) 105 degree
                           ---------------*
 *
CDI8 5 + CC8 + A8b
 *
 *--------------- Reg # 21
                           ---------------*
 *
 *
 *--------------- CDO8; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
CDO8 5 + CC8 - A8b
 *
 *--------------- Reg # 22
                           ---------------*
 *
 *
 *--------------- CDI9; assigned material: Vacuum; mat # (2) 120 degree
                           ---------------*
 *
CDI9 5 + CC9 + A9b
 *
 *--------------- Reg # 23
                           ---------------*
 *
 *
 *--------------- CDO9; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
CDO9 5 + CC9 - A9b
 *
 *--------------- Reg # 24
                           ---------------*
 *
 *
 *--------------- CDI10; assigned material: Vacuum; mat # (2) 135
degree ---------------*
 *
CDI10 5 + CC10 + A10b
 *
 *--------------- Reg # 25
                           ---------------*
 *
 *
 *--------------- CDO10; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
CDO10 5 + CC10 - A10b
 *
 *--------------- Reg # 26
                           ---------------*
 *
 *
 *--------------- CDI11; assigned material: Vacuum; mat # (2) 150
degree ---------------*
 *
CDI11 5 + CC11 + A11b
 *
 *--------------- Reg # 27
                           ---------------*
 *
 *
 *--------------- CDO11; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
CDO11 5 + CC11 - A11b
 *
 *--------------- Reg # 28
                           ---------------*
 *
 *
 *--------------- CDI12; assigned material: Vacuum; mat # (2) 165
degree ---------------*
 *
CDI12 5 + CC12 + A12b
 *
 *--------------- Reg # 29
                           ---------------*
 *
 *
 *--------------- CDO12; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
CDO12 5 + CC12 - A12b
 *
 *--------------- Reg # 30
                           ---------------*
 *
 *
 *--------------- CDI13; assigned material: Vacuum; mat # (2) 180
degree ---------------*
 *
CDI13 5 + CC13 - A13a
 *
 *--------------- Reg # 31
                           ---------------*
 *
 *
 *--------------- CDO13; assigned material: Vacuum; mat # (2)
                           ---------------*
 *
CDO13 5 + CC13 + A13a
  END
 Number of input regions 31
 Number of code zones 31
 Length of integer array 894

 CODE ZONE INPUT REGION ZONE DATA LOC. NO. OF BODIES REGION NO.
      1 1 249 2 1
      2 2 258 15 2
      3 3 319 2 3
      4 4 328 3 4
      5 5 341 2 5
      6 6 350 2 6
      7 7 359 2 7
      8 8 368 2 8
      9 9 377 2 9
     10 10 386 2 10
     11 11 395 2 11
     12 12 404 2 12
     13 13 413 2 13
     14 14 422 2 14
     15 15 431 2 15
     16 16 440 2 16
     17 17 449 2 17
     18 18 458 2 18
     19 19 467 2 19
     20 20 476 2 20
     21 21 485 2 21
     22 22 494 2 22
     23 23 503 2 23
     24 24 512 2 24
     25 25 521 2 25
     26 26 530 2 26
     27 27 539 2 27
     28 28 548 2 28
     29 29 557 2 29
     30 30 566 2 30
     31 31 575 2 31

    I IR1(I) IR2(I)
    1 1 1
    2 2 2
    3 3 3
    4 4 4
    5 5 5
    6 6 6
    7 7 7
    8 8 8
    9 9 9
   10 10 10
   11 11 11
   12 12 12
   13 13 13
   14 14 14
   15 15 15
   16 16 16
   17 17 17
   18 18 18
   19 19 19
   20 20 20
   21 21 21
   22 22 22
   23 23 23
   24 24 24
   25 25 25
   26 26 26
   27 27 27
   28 28 28
   29 29 29
   30 30 30
   31 31 31

 Interpreted body echo

 Body n. 1 PLA A10b Rot. 0
         0.7071068 0.000000 -0.7071068
-60.00225 0.000000 0.000000
 Body n. 2 PLA A11b Rot. 0
         0.4999980 0.000000 -0.8660266
-60.00041 0.000000 0.000000
 Body n. 3 PLA A12b Rot. 0
         0.2588189 0.000000 -0.9659259
-60.00040 0.000000 0.000000
 Body n. 4 XYP A13a Rot. 0
         -60.00000
 Body n. 5 XYP A1b Rot. 0
          60.00000
 Body n. 6 PLA A2b Rot. 0
         0.2588189 0.000000 0.9659259
-60.00066 0.000000 0.000000
 Body n. 7 PLA A3b Rot. 0
         0.4999980 0.000000 0.8660266
-60.00041 0.000000 0.000000
 Body n. 8 PLA A4b Rot. 0
         0.7071068 0.000000 0.7071068
-60.00225 0.000000 0.000000
 Body n. 9 PLA A5b Rot. 0
         0.8660266 0.000000 0.4999980
-60.00041 0.000000 0.000000
 Body n. 10 PLA A6b Rot. 0
         0.9659259 0.000000 0.2588189
-60.00040 0.000000 0.000000
 Body n. 11 YZP A7b Rot. 0
          60.00000
 Body n. 12 PLA A8b Rot. 0
         0.9659259 0.000000 -0.2588189
-60.00040 0.000000 0.000000
 Body n. 13 PLA A9b Rot. 0
         0.8660266 0.000000 -0.4999980
-60.00041 0.000000 0.000000
 Body n. 14 RPP BH1 Rot. 0
         -2500.000 2500.000 -2500.000
 2500.000 -2500.000 2500.000
 Body n. 15 RCC CC1 Rot. 0
          0.000000 0.000000 55.00000
 0.000000 0.000000 100.0000
          6.770000
 Body n. 16 RCC CC10 Rot. 0
          38.89000 0.000000 -38.89000
 70.71000 0.000000 -70.71000
          6.770000
 Body n. 17 RCC CC11 Rot. 0
          27.50000 0.000000 -47.63000
 50.00000 0.000000 -86.60000
          6.770000
 Body n. 18 RCC CC12 Rot. 0
          14.24000 0.000000 -53.13000
 25.88000 0.000000 -96.59000
          6.770000
 Body n. 19 RCC CC13 Rot. 0
          0.000000 0.000000 -155.0000
 0.000000 0.000000 100.0000
          6.770000
 Body n. 20 RCC CC2 Rot. 0
          14.24000 0.000000 53.13000
 25.88000 0.000000 96.59000
          6.770000
 Body n. 21 RCC CC3 Rot. 0
          27.50000 0.000000 47.63000
 50.00000 0.000000 86.60000
          6.770000
 Body n. 22 RCC CC4 Rot. 0
          38.89000 0.000000 38.89000
 70.71000 0.000000 70.71000
          6.770000
 Body n. 23 RCC CC5 Rot. 0
          47.63000 0.000000 27.50000
 86.60000 0.000000 50.00000
          6.770000
 Body n. 24 RCC CC6 Rot. 0
          53.13000 0.000000 14.24000
 96.59000 0.000000 25.88000
          6.770000
 Body n. 25 RCC CC7 Rot. 0
          55.00000 0.000000 0.000000
 100.0000 0.000000 0.000000
          6.770000
 Body n. 26 RCC CC8 Rot. 0
          53.13000 0.000000 -14.24000
 96.59000 0.000000 -25.88000
          6.770000
 Body n. 27 RCC CC9 Rot. 0
          47.63000 0.000000 -27.50000
 86.60000 0.000000 -50.00000
          6.770000
 Body n. 28 XYP P1 Rot. 0
         -7.500000
 Body n. 29 XYP P2 Rot. 0
          7.500000
 Body n. 30 RPP TA Rot. 0
         -1.500000 1.500000 -7.500000
 7.500000 -20.00000 20.00000
 Body n. 31 RPP VA1 Rot. 0
         -2000.000 2000.000 -2000.000
 2000.000 -2000.000 2000.000

 Interpreted region echo

 Region n. 1 BH
                 14 -31
 Region n. 2 VA
                 31 -30 -15 -20 -21 -22 -23
                -24 -25 -26 -27 -16 -17 -18
                -19
 Region n. 3 TA1
                 30 28
 Region n. 4 TA2
                 29 30 -28
 Region n. 5 DE1
                 30 -29
 Region n. 6 CDI1
                 15 5
 Region n. 7 CDO1
                 15 -5
 Region n. 8 CDI2
                 20 6
 Region n. 9 CDO2
                 20 -6
 Region n. 10 CDI3
                 21 7
 Region n. 11 CDO3
                 21 -7
 Region n. 12 CDI4
                 22 8
 Region n. 13 CDO4
                 22 -8
 Region n. 14 CDI5
                 23 9
 Region n. 15 CDO5
                 23 -9
 Region n. 16 CDI6
                 24 10
 Region n. 17 CDO6
                 24 -10
 Region n. 18 CDI7
                 25 11
 Region n. 19 CDO7
                 25 -11
 Region n. 20 CDI8
                 26 12
 Region n. 21 CDO8
                 26 -12
 Region n. 22 CDI9
                 27 13
 Region n. 23 CDO9
                 27 -13
 Region n. 24 CDI10
                 16 1
 Region n. 25 CDO10
                 16 -1
 Region n. 26 CDI11
                 17 2
 Region n. 27 CDO11
                 17 -2
 Region n. 28 CDI12
                 18 3
 Region n. 29 CDO12
                 18 -3
 Region n. 30 CDI13
                 19 -4
 Region n. 31 CDO13
                 19 4

 All region volumes set to 1

           Volumes (cm**3)
1
    Reg. 1 2 3 4 5
6 7 8 9 10
 Volume 1.000E+00 1.000E+00 1.000E+00 1.000E+00 1.000E+00
1.000E+00 1.000E+00 1.000E+00 1.000E+00 1.000E+00

0NGEOM= 4002, NGLAST= 6094

 **** Stars/Energy accumulation arrays start at location 6097 and end
at 6344 (I*4 addr.) ****

 **** Minimum step size array start at location 6347 and end at
6412 (I*4 addr.) ****

 **** Maximum step size array start at location 6415 and end at
6480 (I*4 addr.) ****
GEOEND

 Total time used for geometry initialization: 0.120 s

 ***** Next control card ***** PHYSICS 2.000 0.000 0.000
     13.00 14.00 1.000 DECAYS

 ***** Next control card ***** PHYSICS 1.000 0.000 0.000
     10.00 11.00 1.000 DECAYS

 ***** Next control card ***** PART-THR -1.0000E-09 13.00 14.00
     1.000 0.000 0.000

 ***** Next control card ***** PART-THR -1.0000E-06 10.00 11.00
     1.000 0.000 0.000

 ***** Next control card ***** RANDOMIZ 1.000 2.3996E+07 0.000
     0.000 0.000 0.000

!!!!!!!!!! Seed file not accepted: or corrupted or main seed not matching
the requested one !!!!!!!!!!

  FLRM64 INITIALIZED 0 0 96138 239 23996138

 ***** Next control card ***** ASSIGNMA 1.000 1.000 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 2.000 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 3.000 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 6.000 4.000 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 5.000 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 6.000 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 7.000 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 8.000 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 9.000 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 10.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 11.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 12.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 13.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 14.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 15.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 16.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 17.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 18.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 19.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 20.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 21.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 22.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 23.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 24.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 25.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 26.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 27.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 28.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 29.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 30.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** ASSIGNMA 2.000 31.00 0.000
     0.000 0.000 0.000

 ***** Next control card ***** MUPHOTON 1.000 0.000 0.000
     3.000 25.00 1.000 DECAYS

 ***** Next control card ***** USERDUMP 100.0 0.000 3.000
     0.000 0.000 0.000

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     18.00 19.00 144.0 MUONs90

 ***** Next control card ***** USRBDX 1.000 0.000 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     6.000 7.000 144.0 MUONs0

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     8.000 9.000 144.0 MUONs15

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     10.00 11.00 144.0 MUONs30

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     12.00 13.00 144.0 MUONs45

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     14.00 15.00 144.0 MUONs60

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     16.00 17.00 144.0 MUONs75

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     18.00 19.00 144.0 MUONs90

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     20.00 21.00 144.0 MUONs105

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     22.00 23.00 144.0 MUONs120

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     24.00 25.00 144.0 MUONs135

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     26.00 27.00 144.0 MUONs150

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     28.00 29.00 144.0 MUONs165

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     30.00 31.00 144.0 MUONs180

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     4.000 5.000 9.000 MUONsf

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** USRBDX -1.000 10.00 -49.00
     4.000 2.000 360.0 MUONsl

 ***** Next control card ***** USRBDX 4.1500E-03 3.5600E-03 3.000
     6.283 0.000 1.000 &

 ***** Next control card ***** SOURCE 1.350 0.000 1.350
     0.000 1.800 0.000

 ***** Next control card ***** SOURCE 2.300 0.000 2.300
     0.000 1.700 3.100 &

 ***** Next control card ***** START 1.0000E+08 0.000 0.000
     0.000 0.000 0.000

 Total time used for input reading: 1.900E-02 s

  **** Power exponent for grey particle correlations set at -13.****

  *** Reading evaporation and nuclear data from unit: 14

 **** Nuclear data file for Fluka9x-20xy ****

 File version: 2011.1

 Copyright (C) 1990-2011 by Alfredo Ferrari & Paola Sala

  *** Evaporation: using NNDC (1996) data ***

 Starting location in blank common of LVL data: 6482
 Last location in blank common of LVL data: 9636737

 Starting location in blank common of CE data: 9636738
 Last location in blank common of CE data: 9687509

 Starting location in blank common of alpha data: 9687510
 Last location in blank common of alpha data: 9690269

 Starting location in blank common of gamma data: 9690270
 Last location in blank common of gamma data: 9821217

 Starting location in blank common of beta data: 9821218
 Last location in blank common of beta data: 9863505

 Starting location in blank common of GDR data: 9863506
 Last location in blank common of GDR data: 9918560

 Starting location in blank common of (g,x) data: 9918561
 Last location in blank common of (g,x) data: 10221481

  **** RIPL2/Ign. self-cons. T=0 N,Z-dep. level density used ****
  **** RIPL-2 / Ignyatuk level density en. dep. used ****
  **** with Moller, Nix self-cons set of parameters for T=oo ****
  **** Original Gilbert/Cameron pairing energy used ****

  **** Maximum Fermi momentum : 0.268371314 GeV/c ****

  **** Maximum Fermi energy : 0.0376013778 GeV ****

  **** Average Fermi energy : 0.022676846 GeV ****

  **** Average binding energy : 0.00768006314 GeV ****

  **** Nuclear well depth : 0.04528144 GeV ****

  **** Excess mass for 11-B : 0.00866803993 GeV ****

  **** Cameron E. m. for 11-B : 0.00792484451 GeV ****

  **** Cam.El. E. m. for 11-B : 0.00851833168 GeV ****

  **** My.&Sw. E. m. for 11-B : 0.00887639914 GeV ****

  **** Atomic mass for 11-B : 10.255106 GeV ****

  **** Nuclear mass for 11-B : 10.2525511 GeV ****

  **** Excess mass for 12-C : 0. GeV ****

  **** Cameron E. m. for 12-C : 0.00151353085 GeV ****

  **** Cam.El. E. m. for 12-C : 0.00163579884 GeV ****

  **** My.&Sw. E. m. for 12-C : -0.000383192004 GeV ****

  **** Atomic mass for 12-C : 11.1779318 GeV ****

  **** Nuclear mass for 12-C : 11.1748667 GeV ****

  **** Excess mass for 13-C : 0.00312499981 GeV ****

  **** Cameron E. m. for 13-C : 0.00287424121 GeV ****

  **** Cam.El. E. m. for 13-C : 0.00348056527 GeV ****

  **** My.&Sw. E. m. for 13-C : 0.00355792139 GeV ****

  **** Atomic mass for 13-C : 12.1125507 GeV ****

  **** Nuclear mass for 13-C : 12.1094866 GeV ****

  **** Excess mass for 14-N : 0.00286339992 GeV ****

  **** Cameron E. m. for 14-N : 0.00337313744 GeV ****

  **** Cam.El. E. m. for 14-N : 0.0036975285 GeV ****

  **** My.&Sw. E. m. for 14-N : 0.00286558713 GeV ****

  **** Atomic mass for 14-N : 13.0437841 GeV ****

  **** Nuclear mass for 14-N : 13.0402088 GeV ****

  **** Excess mass for 15-O : 0.00285555003 GeV ****

  **** Cameron E. m. for 15-O : 0.00240658456 GeV ****

  **** Cam.El. E. m. for 15-O : 0.00259008165 GeV ****

  **** My.&Sw. E. m. for 15-O : 0.00332844956 GeV ****

  **** Atomic mass for 15-O : 13.9752703 GeV ****

  **** Nuclear mass for 15-O : 13.9711847 GeV ****

  **** Excess mass for 16-O : -0.00473699998 GeV ****

  **** Cameron E. m. for 16-O : -0.00331055629 GeV ****

  **** Cam.El. E. m. for 16-O : -0.00319385715 GeV ****

  **** My.&Sw. E. m. for 16-O : -0.00483116647 GeV ****

  **** Atomic mass for 16-O : 14.8991718 GeV ****

  **** Nuclear mass for 16-O : 14.8950863 GeV ****

  **** Excess mass for 27-Al : -0.0171969198 GeV ****

  **** Cameron E. m. for 27-Al : -0.0186259765 GeV ****

  **** Cam.El. E. m. for 27-Al : -0.0171393938 GeV ****

  **** My.&Sw. E. m. for 27-Al : -0.017145671 GeV ****

  **** Atomic mass for 27-Al : 25.1331501 GeV ****

  **** Nuclear mass for 27-Al : 25.1265125 GeV ****

  **** Excess mass for 28-Si : -0.0214928202 GeV ****

  **** Cameron E. m. for 28-Si : -0.0220552329 GeV ****

  **** Cam.El. E. m. for 28-Si : -0.0202140864 GeV ****

  **** My.&Sw. E. m. for 28-Si : -0.021535717 GeV ****

  **** Atomic mass for 28-Si : 26.0603485 GeV ****

  **** Nuclear mass for 28-Si : 26.0532017 GeV ****

  **** Excess mass for 40-Ca : -0.0348461308 GeV ****

  **** Cameron E. m. for 40-Ca : -0.0357677415 GeV ****

  **** Cam.El. E. m. for 40-Ca : -0.0336877368 GeV ****

  **** My.&Sw. E. m. for 40-Ca : -0.0349160209 GeV ****

  **** Atomic mass for 40-Ca : 37.224926 GeV ****

  **** Nuclear mass for 40-Ca : 37.2147255 GeV ****

  **** Excess mass for 55-Fe : -0.0574751087 GeV ****

  **** Cameron E. m. for 55-Fe : -0.0595041849 GeV ****

  **** Cam.El. E. m. for 55-Fe : -0.0580860823 GeV ****

  **** My.&Sw. E. m. for 55-Fe : -0.0575032495 GeV ****

  **** Atomic mass for 55-Fe : 51.1747131 GeV ****

  **** Nuclear mass for 55-Fe : 51.1614609 GeV ****

  **** Excess mass for 56-Fe : -0.0606013089 GeV ****

  **** Cameron E. m. for 56-Fe : -0.0623576604 GeV ****

  **** Cam.El. E. m. for 56-Fe : -0.0608849637 GeV ****

  **** My.&Sw. E. m. for 56-Fe : -0.0604862086 GeV ****

  **** Atomic mass for 56-Fe : 52.1030807 GeV ****

  **** Nuclear mass for 56-Fe : 52.0898285 GeV ****

  **** Excess mass for 107-Ag: -0.088405259 GeV ****

  **** Cameron E. m. for 107-Ag: -0.0891378522 GeV ****

  **** Cam.El. E. m. for 107-Ag: -0.0886852369 GeV ****

  **** My.&Sw. E. m. for 107-Ag: -0.0882571116 GeV ****

  **** Atomic mass for 107-Ag: 99.5814896 GeV ****

  **** Nuclear mass for 107-Ag: 99.5576096 GeV ****

  **** Excess mass for 132-Xe: -0.0892794058 GeV ****

  **** Cameron E. m. for 132-Xe: -0.0898088515 GeV ****

  **** Cam.El. E. m. for 132-Xe: -0.0892864987 GeV ****

  **** My.&Sw. E. m. for 132-Xe: -0.0894251093 GeV ****

  **** Atomic mass for 132-Xe: 122.867973 GeV ****

  **** Nuclear mass for 132-Xe: 122.840576 GeV ****

  **** Excess mass for 181-Ta: -0.0484412275 GeV ****

  **** Cameron E. m. for 181-Ta: -0.0481105074 GeV ****

  **** Cam.El. E. m. for 181-Ta: -0.0478131436 GeV ****

  **** My.&Sw. E. m. for 181-Ta: -0.0482191741 GeV ****

  **** Atomic mass for 181-Ta: 168.552032 GeV ****

  **** Nuclear mass for 181-Ta: 168.515137 GeV ****

  **** Excess mass for 208-Pb: -0.0217638295 GeV ****

  **** Cameron E. m. for 208-Pb: -0.0184126478 GeV ****

  **** Cam.El. E. m. for 208-Pb: -0.020333156 GeV ****

  **** My.&Sw. E. m. for 208-Pb: -0.0209293775 GeV ****

  **** Atomic mass for 208-Pb: 193.72905 GeV ****

  **** Nuclear mass for 208-Pb: 193.687683 GeV ****

  **** Excess mass for 209-Bi: -0.0182725303 GeV ****

  **** Cameron E. m. for 209-Bi: -0.0147107309 GeV ****

  **** Cam.El. E. m. for 209-Bi: -0.0171704441 GeV ****

  **** My.&Sw. E. m. for 209-Bi: -0.0177380107 GeV ****

  **** Atomic mass for 209-Bi: 194.664047 GeV ****

  **** Nuclear mass for 209-Bi: 193.687195 GeV ****

  **** Excess mass for 235-U : 0.0409132205 GeV ****

  **** Cameron E. m. for 235-U : 0.0464000776 GeV ****

  **** Cam.El. E. m. for 235-U : 0.0420622788 GeV ****

  **** My.&Sw. E. m. for 235-U : 0.0413222089 GeV ****

  **** Atomic mass for 235-U : 218.942078 GeV ****

  **** Nuclear mass for 235-U : 218.895767 GeV ****

  **** Excess mass for 238-U : 0.0473045185 GeV ****

  **** Cameron E. m. for 238-U : 0.0524553321 GeV ****

  **** Cam.El. E. m. for 238-U : 0.0481762439 GeV ****

  **** My.&Sw. E. m. for 238-U : 0.0473943055 GeV ****

  **** Atomic mass for 238-U : 221.74295 GeV ****

  **** Nuclear mass for 238-U : 221.696655 GeV ****

  **** Evaporation from residual nucleus activated ****
  **** Deexcitation gamma production activated ****
  **** Evaporated "heavies" transport activated ****
  **** High Energy fission requested & activated ****
  **** Fermi Break Up requested & activated ****

 **** Neutrino generators initialized F T T ****

 *** Neutrino xsec file header: Neutrino Xsec file fronm ***
 *** Neutrino xsec file generated on: DATE: 9/10/ 8, TIME: 19:48:1 ***

    Minimum kinetic energy for BME : 1.0000E-03 (GeV/n)
    Overall minimum kinetic energy for ion nuclear interactions:
1.0000E-03 (GeV/n)

  **** Fluorescence data successfully retrieved from unit 13 ****

 **** Subroutine Mulmix: medium n. 6 ****

 Number of elements = 1, Density= 2.00000 (g/cm**3)
0 I Z Pa F_i Rho_i
 Index Atomic Atomic Proportion Proportion
          Number Weight by Number by weight

    1 6.00000 12.0107 1.00000 2.00000

 ZTILDE,AE1O3,BLCCRA= 6.00000E+00 2.29011E+00 6.40294E-03

 ZTILDE,AE1O3,BLCCRE= 5.00000E+00 2.29011E+00 6.40294E-03
 BLCC,XCC,TFFLU0,XR0FLU= 1.20908E+04 9.69872E-04 5.53741E-04
3.95301E-05
 BLCCE,XCCE,TFEMF0,XR0EMF= 1.41059E+04 1.04758E+00 1.41811E-03
8.36853E-02
 Particle n.: -6 Ecutm (prim. & sec.) = 3.747 GeV 3.747
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: -5 Ecutm (prim. & sec.) = 2.828 GeV 2.828
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: -4 Ecutm (prim. & sec.) = 2.829 GeV 2.829
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: -3 Ecutm (prim. & sec.) = 1.896 GeV 1.896
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 1 Ecutm (prim. & sec.) = 0.9583 GeV 0.9583
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 2 Ecutm (prim. & sec.) = 0.9583 GeV 0.9583
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 3 Ecutm (prim. & sec.) = 2.0511E-02 GeV 2.0511E-02
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 4 Ecutm (prim. & sec.) = 2.0511E-02 GeV 2.0511E-02
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 10 Ecutm (prim. & sec.) = 0.1257 GeV 0.1257
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 11 Ecutm (prim. & sec.) = 0.1257 GeV 0.1257
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 13 Ecutm (prim. & sec.) = 0.1596 GeV 0.1596
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 14 Ecutm (prim. & sec.) = 0.1596 GeV 0.1596
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 15 Ecutm (prim. & sec.) = 0.5136 GeV 0.5136
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 16 Ecutm (prim. & sec.) = 0.5136 GeV 0.5136
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 20 Ecutm (prim. & sec.) = 1.217 GeV 1.217
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 21 Ecutm (prim. & sec.) = 1.209 GeV 1.209
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 31 Ecutm (prim. & sec.) = 1.209 GeV 1.209
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 33 Ecutm (prim. & sec.) = 1.217 GeV 1.217
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 36 Ecutm (prim. & sec.) = 1.341 GeV 1.341
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 37 Ecutm (prim. & sec.) = 1.341 GeV 1.341
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 38 Ecutm (prim. & sec.) = 1.692 GeV 1.692
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 39 Ecutm (prim. & sec.) = 1.692 GeV 1.692
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 41 Ecutm (prim. & sec.) = 1.797 GeV 1.797
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 42 Ecutm (prim. & sec.) = 1.797 GeV 1.797
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 45 Ecutm (prim. & sec.) = 1.889 GeV 1.889
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 46 Ecutm (prim. & sec.) = 1.889 GeV 1.889
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 49 Ecutm (prim. & sec.) = 1.988 GeV 1.988
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 50 Ecutm (prim. & sec.) = 1.988 GeV 1.988
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 51 Ecutm (prim. & sec.) = 2.305 GeV 2.305
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 52 Ecutm (prim. & sec.) = 2.488 GeV 2.488
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 54 Ecutm (prim. & sec.) = 2.594 GeV 2.594
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 57 Ecutm (prim. & sec.) = 2.305 GeV 2.305
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 58 Ecutm (prim. & sec.) = 2.488 GeV 2.488
GeV, Hthnsz = 1.0000E+30 GeV
 Particle n.: 60 Ecutm (prim. & sec.) = 2.594 GeV 2.594
GeV, Hthnsz = 1.0000E+30 GeV
 **** Atomic electron contribution accounted via the Fano correction ****
 **** f_Fano = 9.639E+00, Z_Fano = 6.000E+00 ****

 **** Isotope tabulation data start at location 10221482 and end at
10223976 (I*4 addr.) ****

 No radioactive products/decays requested

 Flags for applying biasing to prompt and/or decay radiation:
                        Hadr/muon EM Low en. Neut.
                       Prompt/Decay Prompt/Decay Prompt/Decay
  Inter./decay length: T F T F T F
  Leading Particle : T F T F T F
  Importance and WW : T F T F T F

  EM transport threshold multipliers: prompt decay
                                           1.00E+00 1.00E+00

 **** Non analog absorption factors start at location 10223979 and end
at 10224040 (I*4 addr.) ****

 **** Biased downscattering factors start at location 10224043 and end
at 10224104 (I*4 addr.) ****

 **** Non analog absorption group limits start at location10224105 and end
at 10224135 (I*4 addr.) ****

 **** Biased downscattering group limits start at location10224136 and end
at 10224166 (I*4 addr.) ****

 **** Cut-off group limits start at location 10224167 and end at
10224197 (I*4 addr.) ****

 **** Lower Weight Window limits start at location 10224199 and end at
10224260 (I*4 addr.) ****
1
 ***** Neutron Xsec: group limits, average energies, velocities and
momenta *****
 ***** start at location 10224261, end at location 10226428 (I*4 addr.) *****

 ***** Neutron Xsec: ****
 **** Group limits, average energies, velocities and momenta start at
location 10224261, end at location 10226428 (I*4 addr.) *****

 Group cross sections storage starts at 10233189
 Last location used for group xsecs 10396491

                    *** Values read from the cross section file ***
    Panini independent Xsec

 Number of primary groups 260
 Number of primary downscatters 260
 Number of primary upscatters 30
 Number of secondary groups 42
 Number of secondary downscatters 42
 Number of neutron+gamma groups 302
 Total xsec table length 335
 Loc. of within group (g->g) xsec 34
 Number of media read 278
 Number of Leg. coefficients 6
 Number of discrete angles 3
1
  *** Fluka low energy group transport threshold: 261
      corresponding to an energy threshold of: 1.00001E-14 GeV
1
  *** Fluka to low en. xsec material correspondence: printed atomic
densities are meaningless when used in a compound ***

   Fluka medium Name Xsec medium atomic density Id. 1
    Id. 2 Id. 3
     number number ( at/(cm barn) )

         1 BLCKHOLE 0 0.0000E+00 0
        0 0

         2 VACUUM 1000 0.0000E+00 0
        0 0

         6 CARBON 1 1.0028E-01 6
       -2 296

  *** dp/dx tab. generated up to 8.11 GeV/c/n ***

   *** Barkas Z^3 corrections accounted for ***

   *** Bloch Z^4 corrections accounted for ***

   *** Mott Z - e corrections accounted for ***

   *** Nuclear stopping power accounted for ***

   **** Nuclear form factor 'a la Kelner' selected ****
   **** Standard Coulomb correction selected ****
   **** for charged hadron and muon bremmstrahlung ****

 ***** dp/dx : material number 6 "CARBON " *****

   ***** Average excitation energy : 7.8000E+01 eV, weighted Z/A :
4.9955E-01 *****
   ***** Sternheimer density effect parameters:
                  *****
   ***** X0 = -0.0351, X1 = 2.4860, C = -2.9925, A = 0.2024 m =
3.0036 D0 = 0.1000 *****

   ***** Restricted energy loss tabulated in 98 intervals *****
   ***** Delta ray production activated above 1.0000E-03 GeV *****

   ***** dE/dx fluctuations activated for this medium, level 1 *****
   ***** (up to 2I discrete levels, up to 2 K-edges) *****

   ***** Restricted pair production energy loss added *****
   ***** Exp. pair production activated above 0.0000E+00 GeV *****

   ***** Restricted bremsstrahlung energy loss added *****
   ***** Exp. bremsstrahlung activated above 1.0000E-03 GeV *****

 ***** dp/dx tabulations in blank common start at location 10396495 *****
 ***** end at location 10409430 (I*4 addresses) *****

  *** Range: P_max: 1.77827895 P_min 0.00398107152 ***

 ***** Range tabulations in blank common start at location 10409433 *****
 ***** end at location 10409540 (I*4 addresses) *****

 ***** Sigtab : material number 6 "CARBON " *****

 ***** Muon photonuclear interac. requested *****

 ***** Xsec tabulations in blank common start at location 10409543 *****
 ***** end at location 10417448 (I*4 addresses) for this medium *****

 ***** Total,elastic,inelastic,pair,bremss. macroscopic cross sections
tabulated in 70 intervals *****

 ***** Xsec tabulations in blank common start at location 10409543 *****
 ***** end at location 10417448 (I*4 addresses) *****

 ***** Form Fact. tabulations in blank common start at location10417449 *****
 ***** end at location10478820 (I*4 addresses) *****
    Chem. sym. : C, Z = 6., A = 12.011, PZ = 1.00000E+00 , RHOZ =
2.00000E+00

 *** Blank common cells from 10478821 to 10479041 allocated for an EMF
R*4 tab. array

 *** Blank common cells from 10479042 to 10479333 allocated for an EMF
R*4 tab. array

 *** Blank common cells from 10479334 to 10479642 allocated for an EMF
R*4 tab. array

 *** Blank common cells from 10479643 to 10479951 allocated for an EMF
R*4 tab. array
 Electron Xsecs for EMF medium # 1(CARBON ) tabulated in 311
intervals
 Min kin. energy 1.000E-03 (GeV)Max kin. energy 8.11 (GeV)

 ***** EMF tabulations in blank common start at location10479952 *****
 ***** end at location10507036 (I*4 addresses) *****

1 Quantities/Biasing associated with each media:

 CARBON
      Rho = 2.00000 g/cm**3 Rlc= 21.3485 cm
      Ae = 1.51100 MeV Ue = 8108.70 MeV
      Ap = 0.333333 MeV Up = 8108.19 MeV
      dE/dx fluctuations activated for this medium, level 1
      below the threshold for explicit secondary electron production
     (up to 2I discrete levels, up to 2 K-edges)
1 Correspondence of regions and EMF-FLUKA material numbers and names:
       Region EMF FLUKA

          1 0 VACUUM 1 BLCKHOLE
          2 0 VACUUM 2 VACUUM
          3 0 VACUUM 2 VACUUM
          4 1 CARBON 6 CARBON
     Ecut = 1.5110E+00 MeV, Pcut = 3.3333E-01 MeV, BIAS = F,
Ray. = F, S(q,Z) = T, Pz(q,Z) = F
          5 0 VACUUM 2 VACUUM
          6 0 VACUUM 2 VACUUM
          7 0 VACUUM 2 VACUUM
          8 0 VACUUM 2 VACUUM
          9 0 VACUUM 2 VACUUM
         10 0 VACUUM 2 VACUUM
         11 0 VACUUM 2 VACUUM
         12 0 VACUUM 2 VACUUM
         13 0 VACUUM 2 VACUUM
         14 0 VACUUM 2 VACUUM
         15 0 VACUUM 2 VACUUM
         16 0 VACUUM 2 VACUUM
         17 0 VACUUM 2 VACUUM
         18 0 VACUUM 2 VACUUM
         19 0 VACUUM 2 VACUUM
         20 0 VACUUM 2 VACUUM
         21 0 VACUUM 2 VACUUM
         22 0 VACUUM 2 VACUUM
         23 0 VACUUM 2 VACUUM
         24 0 VACUUM 2 VACUUM
         25 0 VACUUM 2 VACUUM
         26 0 VACUUM 2 VACUUM
         27 0 VACUUM 2 VACUUM
         28 0 VACUUM 2 VACUUM
         29 0 VACUUM 2 VACUUM
         30 0 VACUUM 2 VACUUM
         31 0 VACUUM 2 VACUUM

 Starting location in blank common of bdrx data:10508287
 Last location in blank common of bdrx data: 10508385
1
  === Output before the actual run - Particle properties: ===

  === Transportable Fluka particles: ===

 Particle Number Mass Mean Life Charge Baryon Discard Decay
PDG id
                  (GeV/c**2) (s) number Flag(=1) Flag

 4-HELIUM -6 3.7273803 1.000E+18 2 4 0 1
9999
 3-HELIUM -5 2.8083922 1.000E+18 2 3 0 1
9999
 TRITON -4 2.8089218 1.000E+18 1 3 0 1
9999
 DEUTERON -3 1.8756134 1.000E+18 1 2 0 1
9999
 HEAVYION -2 0.0000000 1.000E+18 0 0 0 1
9999
 OPTIPHOT -1 0.0000000 1.000E+18 0 0 0 1
9999
 RAY 0 0.0000000 0.00 0 0 0 1
9999
 PROTON 1 0.9382723 1.000E+18 1 1 0 1
2212
 APROTON 2 0.9382723 1.000E+18 -1 -1 0 1
-2212
 ELECTRON 3 0.0005110 1.000E+18 -1 0 0 1
 11
 POSITRON 4 0.0005110 1.000E+18 1 0 0 1
-11
 NEUTRIE 5 0.0000000 1.000E+18 0 0 1 1
 12
 ANEUTRIE 6 0.0000000 1.000E+18 0 0 1 1
-12
 PHOTON 7 0.0000000 1.000E+18 0 0 0 1
 22
 NEUTRON 8 0.9395656 889. 0 1 0 1
2112
 ANEUTRON 9 0.9395656 889. 0 -1 0 1
-2112
 MUON+ 10 0.1056584 2.197E-06 1 0 0 1
-13
 MUON- 11 0.1056584 2.197E-06 -1 0 0 1
 13
 KAONLONG 12 0.4976710 5.170E-08 0 0 0 1
130
 PION+ 13 0.1395699 2.603E-08 1 0 0 2
211
 PION- 14 0.1395699 2.603E-08 -1 0 0 2
-211
 KAON+ 15 0.4936460 1.237E-08 1 0 0 1
321
 KAON- 16 0.4936460 1.237E-08 -1 0 0 1
-321
 LAMBDA 17 1.1156300 2.632E-10 0 1 0 1
3122
 ALAMBDA 18 1.1156300 2.632E-10 0 -1 0 1
-3122
 KAONSHRT 19 0.4976710 8.922E-11 0 0 0 1
310
 SIGMA- 20 1.1974300 1.479E-10 -1 1 0 1
3112
 SIGMA+ 21 1.1893700 7.990E-11 1 1 0 1
3222
 SIGMAZER 22 1.1925500 7.400E-20 0 1 0 1
3212
 PIZERO 23 0.1349764 8.400E-17 0 0 0 1
111
 KAONZERO 24 0.4976710 0.00 0 0 0 1
311
 AKAONZER 25 0.4976710 0.00 0 0 0 1
-311
 RESERVED 26 0.1349764 8.400E-17 0 0 0 1
  0
 NEUTRIM 27 0.0000000 1.000E+18 0 0 1 1
 14
 ANEUTRIM 28 0.0000000 1.000E+18 0 0 1 1
-14
 RESERVED 29 0.5474500 0.00 0 0 0 1
  0
 RESERVED 30 0.0000000 0.00 0 0 0 1
  0
 ASIGMA- 31 1.1893700 7.990E-11 -1 -1 0 1
-3222
 ASIGMAZE 32 1.1925500 7.400E-20 0 -1 0 1
-3212
 ASIGMA+ 33 1.1974300 1.479E-10 1 -1 0 1
-3112
 XSIZERO 34 1.3149000 2.900E-10 0 1 0 1
3322
 AXSIZERO 35 1.3149000 2.900E-10 0 -1 0 1
-3322
 XSI- 36 1.3213200 1.639E-10 -1 1 0 1
3312
 AXSI+ 37 1.3213200 1.639E-10 1 -1 0 1
-3312
 OMEGA- 38 1.6724300 8.220E-11 -1 1 0 1
3334
 AOMEGA+ 39 1.6724300 8.220E-11 1 -1 0 1
-3334
 WWLOWNEU 40 0.9395656 889. 0 1 0 1
2112
 TAU+ 41 1.7770000 2.910E-13 1 0 0 1
-15
 TAU- 42 1.7770000 2.910E-13 -1 0 0 1
 15
 NEUTRIT 43 0.0000000 1.000E+18 0 0 1 1
 16
 ANEUTRIT 44 0.0000000 1.000E+18 0 0 1 1
-16
 D+ 45 1.8693000 1.057E-12 1 0 0 1
411
 D- 46 1.8693000 1.057E-12 -1 0 0 1
-411
 D0 47 1.8646000 4.150E-13 0 0 0 1
421
 D0BAR 48 1.8646000 4.150E-13 0 0 0 1
-421
 DS+ 49 1.9683000 4.900E-13 1 0 0 1
431
 DS- 50 1.9683000 4.900E-13 -1 0 0 1
-431
 LAMBDAC+ 51 2.2849000 2.060E-13 1 1 0 1
4122
 XSIC+ 52 2.4679000 4.420E-13 1 1 0 1
4232
 XSIC0 53 2.4710000 1.120E-13 0 1 0 1
4132
 XSIPC+ 54 2.5741000 5.000E-20 1 1 0 1
4322
 XSIPC0 55 2.5788000 5.000E-20 0 1 0 1
4312
 OMEGAC0 56 2.7300000 6.400E-14 0 1 0 1
4332
 ALAMBDC- 57 2.2849000 2.060E-13 -1 -1 0 1
-4122
 AXSIC- 58 2.4679000 4.420E-13 -1 -1 0 1
-4232
 AXSIC0 59 2.4710000 1.120E-13 0 -1 0 1
-4132
 AXSIPC- 60 2.5741000 5.000E-20 -1 -1 0 1
-4322
 AXSIPC0 61 2.5788000 5.000E-20 0 -1 0 1
-4312
 AOMEGAC0 62 2.7300000 6.400E-14 0 -1 0 1
-4332
 RESERVED 63 0.0000000 0.00 0 0 0 1
9999
 RESERVED 64 0.0000000 0.00 0 0 0 1
9999
1
  === Generalised particles (201-233) (for scoring): ===

 Generalised particle Number

 ALL-PART 201
 ALL-CHAR 202
 ALL-NEUT 203
 ALL-NEGA 204
 ALL-POSI 205
 NUCLEONS 206
 NUC&PI+- 207
 ENERGY 208
 PIONS+- 209
 BEAMPART 210
 EM-ENRGY 211
 MUONS 212
 E+&E- 213
 AP&AN 214
 KAONS 215
 STRANGE 216
 KAONS+- 217
 HAD-CHAR 218
 FISSIONS 219
 HE-FISS 220
 LE-FISS 221
 NEU-BALA 222
 HAD-NEUT 223
 KAONS0 224
 C-MESONS 225
 C-(A)BAR 226
 CHARMED 227
 DOSE 228
 UNB-ENER 229
 UNB-EMEN 230
 X-MOMENT 231
 Y-MOMENT 232
 Z-MOMENT 233
 ACTIVITY 234
 ACTOMASS 235
 SI1MEVNE 236
 HADGT20M 237
 NIEL-DEP 238
 DPA-SCO 239
 DOSE-EQ 240
 DOSE-EM 241
 NET-CHRG 242
 DOSEQLET 243
 RES-NIEL 244
 BLANK 245
 BLANK 246
 BLANK 247
 BLANK 248
 BLANK 249
 BLANK 250
1
  === Output before the actual run - Beam properties ===

  Fluka incident beam properties:

    Beam particle: PROTON Id: 1 (Fluka) 2212 (PDG) Charge: 1 Baryon
n.: 1
                   Mass: 0.9383 (GeV/c^2) Mean life: 1.0000E+18 (s)
Weight: 1.000
    Average beam momentum : 2.358489 (GeV/c)
    Average beam kinetic energy: 1.600000 (GeV)
    Momentum deviation at FWHM (rectangular): 0.0000000 (GeV/c)
    Beam hit position : 0.00000000 0.00000000 -25.0000000
     cm
    Beam direction cosines: 0.00000000 0.00000000 1.00000000
    Beam spot FWHM X-width (Gaussian ): 3.0000 cm
    Beam spot FWHM Y-width (Gaussian ): 3.0000 cm
    Beam FWHM angular divergence (Rectangular ): 0.0000 (mrad)
    (Spatial distribution, polarization, and angular direction and
distribution
    are given in the beam frame of reference)

    Beam reference frame (world coordinates):
      Beam X axis: 1.00000000 0.00000000 0.00000000
      Beam Y axis: 0.00000000 1.00000000 0.00000000
      Beam Z axis: 0.00000000 0.00000000 1.00000000

    The nominal beam position belongs to region: 2(VA ),
    lattice cell: 0( )

  === User written source: ===
 The use of a user written source routine has been requested. The beam
features
 listed above could be overridden.

  === Particle transport thresholds:

 Global cut-off kinetic energy for particle transport: 1.000E-02 GeV
 The cut-off kinetic energy is superseded by individual particle
thresholds if set

   Cut-off kinetic energy for 4-HELIUM transport: 1.000E-02 GeV

   Cut-off kinetic energy for 3-HELIUM transport: 1.000E-02 GeV

   Cut-off kinetic energy for TRITON transport: 1.000E-02 GeV

   Cut-off kinetic energy for DEUTERON transport: 1.000E-02 GeV

   Cut-off kinetic energy for PROTON transport: 1.000E-02 GeV

   Cut-off kinetic energy for APROTON transport: 1.000E-02 GeV

   Cut-off kinetic energy for ELECTRON transport defined in the Emfcut card

   Cut-off kinetic energy for POSITRON transport defined in the Emfcut card

   Cut-off kinetic energy for NEUTRIE transport: 0.000E+00 GeV

   Cut-off kinetic energy for ANEUTRIE transport: 0.000E+00 GeV

   Cut-off kinetic energy for PHOTON transport defined in the Emfcut card

   Cut-off kinetic energy for NEUTRON transport: 1.000E-14 GeV

   Cut-off kinetic energy for ANEUTRON transport: 1.000E-05 GeV

   Cut-off kinetic energy for MUON+ transport: 1.000E-06 GeV

   Cut-off kinetic energy for MUON- transport: 1.000E-06 GeV

   Cut-off kinetic energy for KAONLONG transport: 1.000E-02 GeV

   Cut-off kinetic energy for PION+ transport: 1.000E-09 GeV

   Cut-off kinetic energy for PION- transport: 1.000E-09 GeV

   Cut-off kinetic energy for KAON+ transport: 1.000E-02 GeV

   Cut-off kinetic energy for KAON- transport: 1.000E-02 GeV

   Cut-off kinetic energy for LAMBDA transport: 1.000E-02 GeV

   Cut-off kinetic energy for ALAMBDA transport: 1.000E-02 GeV

   Cut-off kinetic energy for KAONSHRT transport: 1.000E-02 GeV

   Cut-off kinetic energy for SIGMA- transport: 1.000E-02 GeV

   Cut-off kinetic energy for SIGMA+ transport: 1.000E-02 GeV

   Cut-off kinetic energy for SIGMAZER transport: 1.000E-02 GeV

   Cut-off kinetic energy for PIZERO transport: 1.000E-02 GeV

   Cut-off kinetic energy for KAONZERO transport: 1.000E-02 GeV

   Cut-off kinetic energy for AKAONZER transport: 1.000E-02 GeV

   Cut-off kinetic energy for RESERVED transport: 1.000E-02 GeV

   Cut-off kinetic energy for NEUTRIM transport: 0.000E+00 GeV

   Cut-off kinetic energy for ANEUTRIM transport: 0.000E+00 GeV

   Cut-off kinetic energy for RESERVED transport: 1.000E-02 GeV

   Cut-off kinetic energy for RESERVED transport: 1.000E-02 GeV

   Cut-off kinetic energy for ASIGMA- transport: 1.000E-02 GeV

   Cut-off kinetic energy for ASIGMAZE transport: 1.000E-02 GeV

   Cut-off kinetic energy for ASIGMA+ transport: 1.000E-02 GeV

   Cut-off kinetic energy for XSIZERO transport: 1.000E-02 GeV

   Cut-off kinetic energy for AXSIZERO transport: 1.000E-02 GeV

   Cut-off kinetic energy for XSI- transport: 1.000E-02 GeV

   Cut-off kinetic energy for AXSI+ transport: 1.000E-02 GeV

   Cut-off kinetic energy for OMEGA- transport: 1.000E-02 GeV

   Cut-off kinetic energy for AOMEGA+ transport: 1.000E-02 GeV

   Cut-off kinetic energy for WWLOWNEU transport: 1.000E-02 GeV

   Cut-off kinetic energy for TAU+ transport: 1.000E-02 GeV

   Cut-off kinetic energy for TAU- transport: 1.000E-02 GeV

   Cut-off kinetic energy for NEUTRIT transport: 0.000E+00 GeV

   Cut-off kinetic energy for ANEUTRIT transport: 0.000E+00 GeV

   Cut-off kinetic energy for D+ transport: 1.000E-02 GeV

   Cut-off kinetic energy for D- transport: 1.000E-02 GeV

   Cut-off kinetic energy for D0 transport: 1.000E-02 GeV

   Cut-off kinetic energy for D0BAR transport: 1.000E-02 GeV

   Cut-off kinetic energy for DS+ transport: 1.000E-02 GeV

   Cut-off kinetic energy for DS- transport: 1.000E-02 GeV

   Cut-off kinetic energy for LAMBDAC+ transport: 1.000E-02 GeV

   Cut-off kinetic energy for XSIC+ transport: 1.000E-02 GeV

   Cut-off kinetic energy for XSIC0 transport: 1.000E-02 GeV

   Cut-off kinetic energy for XSIPC+ transport: 1.000E-02 GeV

   Cut-off kinetic energy for XSIPC0 transport: 1.000E-02 GeV

   Cut-off kinetic energy for OMEGAC0 transport: 1.000E-02 GeV

   Cut-off kinetic energy for ALAMBDC- transport: 1.000E-02 GeV

   Cut-off kinetic energy for AXSIC- transport: 1.000E-02 GeV

   Cut-off kinetic energy for AXSIC0 transport: 1.000E-02 GeV

   Cut-off kinetic energy for AXSIPC- transport: 1.000E-02 GeV

   Cut-off kinetic energy for AXSIPC0 transport: 1.000E-02 GeV

   Cut-off kinetic energy for AOMEGAC0 transport: 1.000E-02 GeV

   Cut-off kinetic energy for RESERVED transport: 1.000E-02 GeV

   Cut-off kinetic energy for RESERVED transport: 1.000E-02 GeV

  "Heavy" residual transport activated

  === Termination conditions: ===

 Maximum cpu-time allocated for this run: 100000000000000000.00 sec
 Minimum cpu-time reserved for output: 10000.00 sec
 Maximum number of beam particles to be followed: 100000000
 Maximum number of stars to be generated: infinite

  === Multiple Coulomb scattering: ===

 Moliere Coulomb scattering for primaries: T
 Moliere Coulomb scattering for secondaries: T

 Hadrons/muons:
 Flag for MCS check with boundary normals: F
 Flag for Coulomb single scattering(s) at boundaries: F
 (# of Coulomb single scattering(s) at boundaries: 1)
 Flag for single scatterings below min. (Moliere) energy: F

  === Electromagnetic Showers: ===

 EM showers are treated by the EMF (A.Fasso`,A.Ferrari,P.R.Sala) code

 Electrons/positrons:
 Flag for MCS check with boundary normals: F
 Flag for Coulomb single scattering(s) at boundaries: F
 (# of Coulomb single scattering(s) at boundaries: 1)
 Flag for single scatterings below min. (Moliere) energy: F

1
  Region Particle importances RR factor Cut off N.A.
abs. N.A. abs. Bias. Dow. Bias. Dow.
  number Fluka part. EM part. Low en. n. group
group factor group factor

       1 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

       2 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

       3 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

       4 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

       5 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

       6 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

       7 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

       8 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

       9 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      10 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      11 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      12 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      13 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      14 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      15 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      16 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      17 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      18 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      19 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      20 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      21 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      22 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      23 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      24 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      25 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      26 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      27 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      28 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      29 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      30 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

      31 1.0000 1.0000 1.0000 261 230
      9.500E-01 0 1.500E+00

 ******* "usrbin" option:

 No user binning defined

 ******* "USRBDX" option:

   Bdrx n. 1 "MUONs90 " , generalized particle n. 10, from region
n. 18 to region n. 19
      detector area: 1.4400E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 1.0000E-03 to 1.0000E+00 GeV, 3
bins (ratio : 1.0000E+01)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 2 "MUONs0 " , generalized particle n. 10, from region
n. 6 to region n. 7
      detector area: 1.4400E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 3 "MUONs15 " , generalized particle n. 10, from region
n. 8 to region n. 9
      detector area: 1.4400E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 4 "MUONs30 " , generalized particle n. 10, from region
n. 10 to region n. 11
      detector area: 1.4400E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 5 "MUONs45 " , generalized particle n. 10, from region
n. 12 to region n. 13
      detector area: 1.4400E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 6 "MUONs60 " , generalized particle n. 10, from region
n. 14 to region n. 15
      detector area: 1.4400E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 7 "MUONs75 " , generalized particle n. 10, from region
n. 16 to region n. 17
      detector area: 1.4400E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 8 "MUONs90 " , generalized particle n. 10, from region
n. 18 to region n. 19
      detector area: 1.4400E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 9 "MUONs105 " , generalized particle n. 10, from region
n. 20 to region n. 21
      detector area: 1.4400E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 10 "MUONs120 " , generalized particle n. 10, from region
n. 22 to region n. 23
      detector area: 1.4400E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 11 "MUONs135 " , generalized particle n. 10, from region
n. 24 to region n. 25
      detector area: 1.4400E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 12 "MUONs150 " , generalized particle n. 10, from region
n. 26 to region n. 27
      detector area: 1.4400E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 13 "MUONs165 " , generalized particle n. 10, from region
n. 28 to region n. 29
      detector area: 1.4400E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 14 "MUONs180 " , generalized particle n. 10, from region
n. 30 to region n. 31
      detector area: 1.4400E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 15 "MUONsf " , generalized particle n. 10, from region
n. 4 to region n. 5
      detector area: 9.0000E+00 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

   Bdrx n. 16 "MUONsl " , generalized particle n. 10, from region
n. 4 to region n. 2
      detector area: 3.6000E+02 cm**2
      this is a one way only estimator
      this is a current like estimator
      logar. energy binning from 3.5600E-03 to 4.1500E-03 GeV, 3
bins (ratio : 1.0524E+00)
      linear angular binning from 0.0000E+00 to 6.2832E+00 sr , 1
bins ( 6.2832E+00 sr wide )
      data will be printed on unit -49 (unformatted if < 0)

 ******* "USRTRACK" option:

 No user track-length estimator defined

 ******* "USRCOLL" option:

 No user collision density estimator defined

 ******* "Usryield" option:

 No user yield estimator defined

 ******* "RESNUCLEI" option:

 No residual nuclei estimator defined

 ******* "Detect" option:

 No detector defined

  === Material compositions: ===

 Material Atomic Atomic Density
Inelastic Elastic Radiation Inelastic
 Number&Name Number Weight
Scattering Scattering Length Scattering
                                                                     Length
for
   
Length
for
     
     
     
  
Length
for
                                                                     PROTON
  at
   
PROTON
  at
     
     
     
  
neutrons
at
                                                                     Beam
energy
    
Beam
energy
     
     
     
   
Threshold
                                                                                                                        Momentum

                                                     g/cm**3 cm
              cm
         cm
    cm

  1 BLCKHOLE 0.000 0.000 0.000
0.1000E+31 0.1000E+31 0.1000E+31 0.1000E+31
  2 VACUUM 0.000 0.000 0.000
0.1000E+31 0.1000E+31 0.1000E+31 0.1000E+31
  3 HYDROGEN 1.000 1.008 0.8370E-04
0.7337E+06 0.1004E+07 0.7532E+06 0.8508E+09
  4 HELIUM 2.000 4.003 0.1660E-03
0.3604E+06 0.4716E+07 0.5682E+06 0.6024E+34
  5 BERYLLIU 4.000 9.012 1.848 37.00
           91.83 35.28 17.26
  6 CARBON 6.000 12.01 2.000 38.51
           122.9 21.35 18.23
  7 NITROGEN 7.000 14.01 0.1170E-02
0.6869E+05 0.2073E+06 0.3247E+05 0.3319E+05
  8 OXYGEN 8.000 16.00 0.1330E-02
0.6269E+05 0.1790E+06 0.2574E+05 0.3013E+05
  9 MAGNESIU 12.00 24.30 1.740 54.05
           126.5 14.39 26.58
 10 ALUMINUM 13.00 26.98 2.699 35.94
           80.05 8.896 17.24
 11 IRON 26.00 55.84 7.874 15.49
           25.93 1.757 9.128
 12 COPPER 29.00 63.55 8.960 14.11
           23.20 1.436 8.423
 13 SILVER 47.00 107.9 10.50 14.12
           21.79 0.8543 10.59
 14 SILICON 14.00 28.09 2.329 42.18
           92.01 9.370 20.38
 15 GOLD 79.00 197.0 19.32 9.180
           13.45 0.3344 7.012
 16 MERCURY 80.00 200.6 13.55 13.17
           19.24 0.4752 9.852
 17 LEAD 82.00 207.2 11.35 15.87
           23.07 0.5612 12.03
 18 TANTALUM 73.00 180.9 16.65 10.38
           15.39 0.4094 7.390
 19 SODIUM 11.00 22.99 0.9710 95.29
           229.1 28.56 47.77
 20 ARGON 18.00 39.95 0.1660E-02
0.6620E+05 0.1230E+06 0.1178E+05 0.3754E+05
 21 CALCIUM 20.00 40.08 1.550 70.98
           131.7 10.42 36.39
 22 TIN 50.00 118.7 7.310 20.86
           32.01 1.206 14.37
 23 TUNGSTEN 74.00 183.8 19.30 8.997
           13.31 0.3504 6.172
 24 TITANIUM 22.00 47.87 4.540 25.62
           44.70 3.560 15.11
 25 NICKEL 28.00 58.69 8.902 13.90
           23.08 1.424 8.419

  === Regions: materials and fields ===

 Region N. and Name Material N. and Name Magn./El. Field (on/off)
         (Mat. N. and Name Magn./El. Field (on/off) for radioactive products)
                                                Minimum and Maximum step
size (cm)
     1 BH 1 BLCKHOLE OFF 0.00000E+00 9.99852E+04
                  ( 1 BLCKHOLE OFF )
     2 VA 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
     3 TA1 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
     4 TA2 6 CARBON OFF 0.00000E+00 9.99852E+04
                  ( 6 CARBON OFF )
     5 DE1 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
     6 CDI1 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
     7 CDO1 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
     8 CDI2 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
     9 CDO2 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    10 CDI3 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    11 CDO3 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    12 CDI4 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    13 CDO4 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    14 CDI5 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    15 CDO5 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    16 CDI6 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    17 CDO6 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    18 CDI7 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    19 CDO7 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    20 CDI8 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    21 CDO8 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    22 CDI9 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    23 CDO9 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    24 CDI10 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    25 CDO10 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    26 CDI11 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    27 CDO11 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    28 CDI12 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    29 CDO12 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    30 CDI13 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )
    31 CDO13 2 VACUUM OFF 0.00000E+00 9.99852E+04
                  ( 2 VACUUM OFF )

  === End of the output associated with the input ===

 Total time used for initialization: 0.724 s

1NUMBER OF BEAM NUMBER OF BEAM APPROXIMATE NUMBER AVERAGE
TIME USED TIME LEFT (RESERVED NUMBER OF STARS
 PARTICLES HANDLED PARTICLES LEFT OF BEAM PARTICLES BY A
BEAM PARTICLE 10000.0 SECONDS CREATED
                                            THAT CAN STILL BE
             FOR PRINTOUT)
                                            HANDLED

 NEXT SEEDS: 0 0 0 0 0 0 1778A
EF 0 0
          1 99999999 99999999
0.0000000E+00 1.0000000E+30 0
 NEXT SEEDS: 200 0 0 0 0 0 1778A
EF 0 0
  *** Frmbrk: we are dealing with a bag of 7 96.6485596
  identical nucleons, go on folks! ***
    2000000 98000000 98000000
3.8159348E-04 1.0000000E+30 916096
 NEXT SEEDS: 85832D1 2 0 0 0 0 1778A
EF 0 0
  *** Frmbrk: we are dealing with a bag of 7 63.6098061
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 73.2082825
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 72.9672775
  identical nucleons, go on folks! ***
    4000000 96000000 96000000
3.8149625E-04 1.0000000E+30 1831970
 NEXT SEEDS:10A5B96F 4 0 0 0 0 1778A
EF 0 0
  *** Frmbrk: we are dealing with a bag of 7 144.556625
  identical nucleons, go on folks! ***
    6000000 94000000 94000000
3.8149532E-04 1.0000000E+30 2747505
 NEXT SEEDS:18EB4407 6 0 0 0 0 1778A
EF 0 0
  *** Frmbrk: we are dealing with a bag of 7 82.6904068
  identical nucleons, go on folks! ***
    8000000 92000000 92000000
3.8149075E-04 1.0000000E+30 3663719
 NEXT SEEDS:213B7738 8 0 0 0 0 1778A
EF 0 0
  *** Frmbrk: we are dealing with a bag of 7 39.6735344
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 44.9836006
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 31.9405842
  identical nucleons, go on folks! ***
   10000000 90000000 90000000
3.8153850E-04 1.0000000E+30 4581013
 NEXT SEEDS:29AB1E15 A 0 0 0 0 1778A
EF 0 0
  *** Frmbrk: we are dealing with a bag of 8 150.789124
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 103.434158
  identical nucleons, go on folks! ***
   12000000 88000000 88000000
3.8151949E-04 1.0000000E+30 5496886
 NEXT SEEDS:31E48088 C 0 0 0 0 1778A
EF 0 0
 Abort called from ICLSSF reason NO CHANNEL SELECTED Run stopped!
 STOP NO CHANNEL SELECTED

--------------060208090203010109010204
Content-Type: text/plain;
 name="sourceE.f"
Content-Transfer-Encoding: 7bit
Content-Disposition: attachment;
 filename="sourceE.f"

*$ CREATE SOURCE.FOR
*COPY SOURCE
*
*=== source ===========================================================*
*
      SUBROUTINE SOURCE ( NOMORE )

      INCLUDE '(DBLPRC)'
      INCLUDE '(DIMPAR)'
      INCLUDE '(IOUNIT)'
*
*----------------------------------------------------------------------*
* *
* Copyright (C) 1990-2009 by Alfredo Ferrari & Paola Sala *
* All Rights Reserved. *
* *
* *
* New source for FLUKA9x-FLUKA20xy: *
* *
* Created on 07 january 1990 by Alfredo Ferrari & Paola Sala *
* Infn - Milan *
* *
* Last change on 08-feb-09 by Alfredo Ferrari *
* *
* This is just an example of a possible user written source routine. *
* note that the beam card still has some meaning - in the scoring the *
* maximum momentum used in deciding the binning is taken from the *
* beam momentum. Other beam card parameters are obsolete. *
* *
* Output variables: *
* *
* Nomore = if > 0 the run will be terminated *
* *
*----------------------------------------------------------------------*
*
      INCLUDE '(BEAMCM)'
      INCLUDE '(FHEAVY)'
      INCLUDE '(FLKSTK)'
      INCLUDE '(IOIOCM)'
      INCLUDE '(LTCLCM)'
      INCLUDE '(PAPROP)'
      INCLUDE '(SOURCM)'
      INCLUDE '(SUMCOU)'

********************USER defined variables**************************
      INCLUDE '(CASLIM)'
* Some variables defined in START card
* Here Ncases is used
********************************************************************
*
      LOGICAL LFIRST
*

      SAVE LFIRST
      DATA LFIRST / .TRUE. /

********************USER defined variables******************************
*angle divergence of x and y
      common/angdivs/xpp,ypp
************************************************************************

*======================================================================*
* *
* BASIC VERSION *
* *
*======================================================================*
      NOMORE = 0
* +-------------------------------------------------------------------*
* | First call initializations:
      IF ( LFIRST ) THEN
* | *** The following 3 cards are mandatory ***
         TKESUM = ZERZER
         LFIRST = .FALSE.
         LUSSRC = .TRUE.
* | *** User initialization ***
* WRITE(*,*) 'Hello world!'
* OPEN(32,FILE='coor.txt',STATUS='NEW',FORM='FORMATTED')
* WRITE(*,*) Ncases
* write(*,*) whasou(1), whasou(2), whasou(3), whasou(4)

* h and (aah, bbh) are the boundaries
* For beam core of Gaussian distribution, 97% is integrated by r from
-b*sigma to b*sigma
      aac = 0.0
      bbc = WHASOU(5)*2.355/WHASOU(1)

* For beam halo of Gaussian distribution, 3% is integrated by r from 0 to
2.649*sigma
* aah = 0.0
      aah = WHASOU(11) * 2.355 / WHASOU(7)
      bbh = WHASOU(12) * 2.355 / WHASOU(9)
      write(*,*) 'Beam core parameters for inner and outer
     & boundaries:', aac, bbc
      write(*,*) 'Beam halo parameters for inner and outer
     & boundaries:', aah, bbh

      END IF
* |
* +-------------------------------------------------------------------*
* Push one source particle to the stack. Note that you could as well
* push many but this way we reserve a maximum amount of space in the
* stack for the secondaries to be generated
* Npflka is the stack counter: of course any time source is called it
* must be =0
      NPFLKA = NPFLKA + 1
* Wt is the weight of the particle
      WTFLK (NPFLKA) = ONEONE
      WEIPRI = WEIPRI + WTFLK (NPFLKA)
* Particle type (1=proton.....). Ijbeam is the type set by the BEAM
* card
* +-------------------------------------------------------------------*
* | (Radioactive) isotope:
      IF ( IJBEAM .EQ. -2 .AND. LRDBEA ) THEN
         IARES = IPROA
         IZRES = IPROZ
         IISRES = IPROM
         CALL STISBM ( IARES, IZRES, IISRES )
         IJHION = IPROZ * 1000 + IPROA
         IJHION = IJHION * 100 + KXHEAV
         IONID = IJHION
         CALL DCDION ( IONID )
         CALL SETION ( IONID )
* |
* +-------------------------------------------------------------------*
* | Heavy ion:
      ELSE IF ( IJBEAM .EQ. -2 ) THEN
         IJHION = IPROZ * 1000 + IPROA
         IJHION = IJHION * 100 + KXHEAV
         IONID = IJHION
         CALL DCDION ( IONID )
         CALL SETION ( IONID )
         ILOFLK (NPFLKA) = IJHION
* | Flag this is prompt radiation
         LRADDC (NPFLKA) = .FALSE.
* | Group number for "low" energy neutrons, set to 0 anyway
         IGROUP (NPFLKA) = 0
* |
* +-------------------------------------------------------------------*
* | Normal hadron:
      ELSE
         IONID = IJBEAM
         ILOFLK (NPFLKA) = IJBEAM
* | Flag this is prompt radiation
         LRADDC (NPFLKA) = .FALSE.
* | Group number for "low" energy neutrons, set to 0 anyway
         IGROUP (NPFLKA) = 0
      END IF
* |
* +-------------------------------------------------------------------*
* From this point .....
* Particle generation (1 for primaries)
      LOFLK (NPFLKA) = 1
* User dependent flag:
      LOUSE (NPFLKA) = 0
* User dependent spare variables:
      DO 100 ISPR = 1, MKBMX1
         SPAREK (ISPR,NPFLKA) = ZERZER
 100 CONTINUE
* User dependent spare flags:
      DO 200 ISPR = 1, MKBMX2
         ISPARK (ISPR,NPFLKA) = 0
 200 CONTINUE
* Save the track number of the stack particle:
      ISPARK (MKBMX2,NPFLKA) = NPFLKA
      NPARMA = NPARMA + 1
      NUMPAR (NPFLKA) = NPARMA
      NEVENT (NPFLKA) = 0
      DFNEAR (NPFLKA) = +ZERZER
* ... to this point: don't change anything
* Particle age (s)
      AGESTK (NPFLKA) = +ZERZER
      AKNSHR (NPFLKA) = -TWOTWO
* Kinetic energy of the particle (GeV)
      TKEFLK (NPFLKA) = SQRT ( PBEAM**2 + AM (IONID)**2 ) - AM (IONID)
* Particle momentum
      PMOFLK (NPFLKA) = PBEAM
* PMOFLK (NPFLKA) = SQRT ( TKEFLK (NPFLKA) * ( TKEFLK (NPFLKA)
* & + TWOTWO * AM (IONID) ) )

      Npercent = INT(NCASES * 0.993)

      IF (Ncase .LE. Npercent) THEN

* Particle coordinates
* Disbx and disby are the boundaries of x and y
* For beam core of Gaussian distribution, 97% is integrated by x or y from
-h*sigma to h*sigma
* h = WHASOU(5)
* Disbx = h*WHASOU(1)/2.355

* Obtain the x coordinate
* CALL Cooxy(WHASOU(1),WHASOU(3),aac,bbc,coox,cooy)
* coox = 0.0
* cooy = 0.0

* Cosines (tx,ty,tz)
* Epx and Epy are the emittances of x and y(UNIT: Pi cm mrad)
* Epx = Pi * 3sigmax *3sigmax'
* Epy = Pi * 3sigmay *3sigmay'
* Obtain the x' and y' of beam core

       Epx = 8.1D0
       Epy = 8.1D0
* coeff is the ratio coefficiet boundary in order to make the same ratio
boundary
       coeff = WHASOU(5)/(WHASOU(1)/2.355)
       WHASOU(2) = 2.355 * (Epx / (coeff * WHASOU(5)*3.1415926d0))
       WHASOU(4) = 2.355 * (Epy / (coeff *
     & (WHASOU(5)*WHASOU(3)/WHASOU(1))*3.1415926d0))

* write(*,*)WHASOU(2),WHASOU(4)
* CALL coxy(WHASOU(2),WHASOU(4),xpp,ypp,cox,coy)

* CALL coxp(WHASOU(1),WHASOU(2),coox,xp)
* CALL coxp(WHASOU(3),WHASOU(4),cooy,yp)
        CALL cxyp(WHASOU(1),WHASOU(2),WHASOU(3),WHASOU(4),
     & aac,bbc,coox,cooy,xpp,ypp)

      ELSE

* Obtain the x and y coordinate of beam halo
* CALL Cooxy(WHASOU(7),WHASOU(9),aah,bbh,coox,cooy)

* Obtain the x' and y' of beam halo
* Epx = 35.D0
* Epy = 35.D0
*
      coeff = WHASOU(12)/(WHASOU(7)/2.355)
* WHASOU(8) = 2.355 * (Epx / (coeff * WHASOU(12)*3.1415926d0))
* WHASOU(10) = 2.355 * (Epy / (coeff *
* & (WHASOU(12)*WHASOU(9)/WHASOU(7))*3.1415926d0))
* Don't defined the emmittance of halo, make the same ratio for (sx_core /
sx_halo) and
* (xp_core/xp_halo), therefore halo ellipse and core ellipse can link
together.

      WHASOU(8) = WHASOU(7) * WHASOU(2) / WHASOU(1)
      WHASOU(10) = WHASOU(9) * WHASOU(4) / WHASOU(3)
* write(*,*)WHASOU(2),WHASOU(4)

* CALL coxp(WHASOU(7),WHASOU(8),coox,xp)
* CALL coxp(WHASOU(9),WHASOU(10),cooy,yp)
        CALL cxyp(WHASOU(7),WHASOU(8),WHASOU(9),WHASOU(10),
     & aah,bbh,coox,cooy,xpp,ypp)

      END IF
* write(*,*)coeff,WHASOU(2),WHASOU(4),WHASOU(8),WHASOU(10)
* write(*,*) 'Current number of beam particles:', Ncase
* write(32,FMT='(4(1X,F12.5))') coox*10.,xpp,cooy*10.,ypp
* write(*,*) coox, cooy,ZBEAM

* xpp = 0.001 * xpp
* ypp = 0.001 * ypp
* cosx = xpp / sqrt(xpp**2+ypp**2+1.0D0)
* cosy = ypp / sqrt(xpp**2+ypp**2+1.0D0)
      cox = 0.0d0
      coy = 0.0d0

* Cosines (tx,ty,tz)
* TXFLK (NPFLKA) = UBEAM
* TYFLK (NPFLKA) = VBEAM
* TZFLK (NPFLKA) = WBEAM
      TXFLK (NPFLKA) = cox
      TYFLK (NPFLKA) = coy
      TZFLK (NPFLKA) = SQRT ( ONEONE - TXFLK (NPFLKA)**2
     & - TYFLK (NPFLKA)**2 )

* Polarization cosines:
      TXPOL (NPFLKA) = -TWOTWO
      TYPOL (NPFLKA) = +ZERZER
      TZPOL (NPFLKA) = +ZERZER

* Particle coordinates
* XFLK (NPFLKA) = XBEAM
* YFLK (NPFLKA) = YBEAM
* ZFLK (NPFLKA) = ZBEAM

      XFLK (NPFLKA) = coox
      YFLK (NPFLKA) = cooy
      ZFLK (NPFLKA) = ZBEAM

* Calculate the total kinetic energy of the primaries: don't change
      IF ( ILOFLK (NPFLKA) .EQ. -2 .OR. ILOFLK (NPFLKA) .GT. 100000 )
     & THEN
         TKESUM = TKESUM + TKEFLK (NPFLKA) * WTFLK (NPFLKA)
      ELSE IF ( ILOFLK (NPFLKA) .NE. 0 ) THEN
         TKESUM = TKESUM + ( TKEFLK (NPFLKA) + AMDISC (ILOFLK(NPFLKA)) )
     & * WTFLK (NPFLKA)
      ELSE
         TKESUM = TKESUM + TKEFLK (NPFLKA) * WTFLK (NPFLKA)
      END IF
      RADDLY (NPFLKA) = ZERZER
* Here we ask for the region number of the hitting point.
* NREG (NPFLKA) = ...
* The following line makes the starting region search much more
* robust if particles are starting very close to a boundary:
      CALL GEOCRS ( TXFLK (NPFLKA), TYFLK (NPFLKA), TZFLK (NPFLKA) )
      CALL GEOREG ( XFLK (NPFLKA), YFLK (NPFLKA), ZFLK (NPFLKA),
     & NRGFLK(NPFLKA), IDISC )
* Do not change these cards:
      CALL GEOHSM ( NHSPNT (NPFLKA), 1, -11, MLATTC )
      NLATTC (NPFLKA) = MLATTC
      CMPATH (NPFLKA) = ZERZER
      CALL SOEVSV
      RETURN
*=== End of subroutine Source =========================================*
      END

*************************************************************************
* Give a cosines of x, y
      subroutine coxy(xdiv, ydiv, xpp, ypp, cosx, cosy)

* cosx and cosy are the cosines of x and y direction
* xp and yp are the angle divergences, xp = Px/Pz, yp =Py/Pz
* xdiv is FWHM of gaussian distribution of xp(unit: mrad)
* ydiv is FWHM of gaussian distribution of yp(unit: mrad)
c parameter(PIPIPI = 3.141592653589793238D0)
c parameter(TWOPIP = 2 * PIPIPI)

      double precision xdiv, ydiv, xp, yp, cosx, cosy
      double precision RGAUSx, RGAUSy,xpp,ypp

* WRITE(*,*)xdiv,ydiv
      CALL FLNRR2(RGAUSx,RGAUSy)
* 0.001 : transform mrad to rad

       xp = 0.001 * xdiv * RGAUSx / 2.355D0
* divergent beam
       yp = 0.001 * ydiv * RGAUSy / 2.355D0
* focusing beam
* yp = - 0.001 * ydiv * RGAUSy / 2.355D0

      cosx = xp / sqrt(xp**2+yp**2+1.0D0)
      cosy = yp / sqrt(xp**2+yp**2+1.0D0)

      xpp = xp * 1000.0
      ypp = yp * 1000.0
      return

      end

*************************************************************************
* A 2D-gaussian annular distribution with inter and outer radii of a and b
      subroutine Cooxy(fwhmx,fwhmy,a,b,coox,cooy)
* note: a<b
* a, b and inner and outer cut-off position in polar coordinate system
* fwhmx,fwhmy are FWHMs of gaussian distribution of x and y(unit: cm)
* sx,sy are the sigma of gaussian distribution
* Xmin = a * sx
* Xmax = b * sx
* Ymin = a * sy
* Ymax = b * sy

      PARAMETER(PI = 3.1415926535897932384626433832795D0)
      double precision a, b, fwhmx,sx,fwhmy,sy,r,the
      double precision XRAND1,XRAND2, coox, cooy

      sx = fwhmx / 2.355D0
      sy = fwhmy / 2.355D0

      XRAND1 = FLRNDM(XDUMMY1)

      r = DSQRT(-2.0*DLOG((1.0D0 - XRAND1)*DEXP(-a**2/2.)
     & + XRAND1*DEXP(-b**2/2.)))

      XRAND2 = FLRNDM(XDUMMY2)
      the = 2.0 * PI * XRAND2

      coox = r * sx * DCOS(THE)
      cooy = r * sy * DSIN(THE)

      return

      end

*************************************************************************
* A 2D-gaussian annular distribution with inter and outer radii of a and b
      subroutine cxyp(fwhmx,fwhmxp,fwhmy,fwhmyp,a,b,coox,cooy,xpp,ypp)
* note: a<b
* a, b and inner and outer cut-off position in polar coordinate system
* fwhmx,fwhmy are FWHMs of gaussian distribution of x and y(unit: cm)
* sx,sy are the sigma of gaussian distribution
* Xmin = a * sx
* Xmax = b * sx
* Ymin = a * sy
* Ymax = b * sy

      PARAMETER(PI = 3.1415926535897932384626433832795D0)
      double precision a, b, fwhmx,fwhmxp,sx,fwhmy,fwhmyp,sy,r,the
      double precision XRAND1,XRAND2, coox, cooy,xp,yp,xpp,ypp

      sx = fwhmx / 2.355D0
      sy = fwhmy / 2.355D0
      xp = fwhmxp / 2.355D0
      yp = fwhmyp / 2.355D0

      XRAND1 = FLRNDM(DUMMY1)

      r = DSQRT(-2.0*DLOG((1.0D0 - XRAND1)*DEXP(-a**2/2.)
     & + XRAND1*DEXP(-b**2/2.)))

      XRAND2 = FLRNDM(DUMMY2)
      the = 2.0 * PI * XRAND2

      coox = r * sx * DCOS(THE)
      xpp = r * xp * DSIN(THE)
      cooy = r * sy * DSIN(THE)
      ypp = r * yp * DCOS(THE)

      return

      end

--------------060208090203010109010204
Content-Type: text/plain;
 name="ranmuonAngR113001"
Content-Transfer-Encoding: 7bit
Content-Disposition: attachment;
 filename="ranmuonAngR113001"

       0 0 1778A EFFE91D916
      61 21 0 0
2D4963283FC2A73354EAA7823FD8D734AF0276783FDC1745A5CF4BFA3FDAF388
77667DD03FA886AC49978B903FC5F9D8477B49683FC95420CD5A98983FE2A6B3
D4FE2E643FEE7A933B5DA51A3FE81C812FAC67943FD9738C1271A6D03FDF3E43
261637563FED73DA2B59B3CF3FE3DD27EBAB96383FDE715198A52A8E3FDA94DE
4734A6883FB30E146A2D89803FC0A9F2151F3B5E3FE9710EC3C7566C3FC474D1
3AD148BA3FEBCFECBB5827763FD41C48438B4CEA3FE88923 4686E2E3FD52C33
9BFC9CE03FBF13B7 8A42B0D3FE30B044506D0063FE623E8AFFE85303FD50635
5A885B8B3FE099A6A81A55603FD1D2CF1A86CFF33FEA9ED6C76877C03FD2C79A
94D5480D3FE300A9761CC7043FE4D814 B8D93F13FEA9E445DBBBC003FA1F9B8
DA870D3A3FDED861B8DE1C463FDED61E1582D2103FB462E1F318E34A3FE58BAA
2564867C3FEEABF37D86B2A43FC5E91C1EB817F43FCFB87135CB21403FCB49B7
7E5116B13FE00E6E32A5EEE03FAA022B6AFD2B2A3FD0CE7B A9440383FBE792D
BF0C416C3FC10EE52CB15CDB3FEDA55F5A557C9E3FE585A739B95D503FD253FE
3177DF413FEDBB5089ED899C3FC2360235DF865B3FEEEEEA D430D943FD768DC
CE712DFD3FE4B4774E55C1763FED08498FB5E4373FEAAB3E8C5C47603FB2BA1F
472851843FDF57D44BC949E93FE15E10 F4C9EB83FB89A26B1ECBA803FA26238
27F4C5F33FE437D22764B9663FD76A5E196AD5A03FA141015F407C2F3FE37A77
6A3A51423FDC7F5F2EEFF7483FE303EBFE2E6AF03FA78A712CCDB28E3FDD08A5
1D53B9663FE89D5C 1BA1E6D3FED4D3C53E46E343FCB64E2B89C75AF3FE05708
90F8D5A23FEF7AA0 17CE3003FA2EF0C26A1735C3FDB3440E8155B603FB3BED5
70D9F0D23FE3E8997F12C3583FC7046C844588C03F93F2A2 F1E5FD13FE2F1F3
A2F379603FC041CC994666373FE5233DEFF11F743FD8A3DEDFB70BE43FC14395
6467C3613FEEADBBB05765363FDC18DC59C7AB523FE92FB471E35BCC3FD72B13
38635A6E3FE47536516ABDF83FD64B8DB2C033F43FEDA43AE1A254993FE6587D
967B21C63FD16EE6

--------------060208090203010109010204--
Received on Tue Aug 09 2011 - 18:09:39 CEST

This archive was generated by hypermail 2.2.0 : Tue Aug 09 2011 - 18:09:39 CEST