Re: One of jobs stop abnormally

From: Hantao Jing <jinght_at_mail.ihep.ac.cn>
Date: Sat, 15 May 2010 09:18:34 +0800

Dear Sir,
       Sorry to forget attach input file.
      This time, I give the files in attachments. Thank you very much!
                                                  Hantao Jing
                                                 2010-5-15

Mario Santana Leitner wrote:
>
> The files were not attached.
> We also need the input file and, if you have any, the user subroutines.
>
>
> -----Original Message-----
> From: owner-fluka-discuss_at_mi.infn.it on behalf of Hantao Jing
> Sent: Fri 5/14/2010 5:08 AM
> To: fluka-discuss_at_fluka.org
> Subject: One of jobs stop abnormally
>
> Dear fluka experts,
> I run about 60 jobs on a farm. But only one stop abnormally. The
> error message is :
> "Abort called from ICLSSF reason NO CHANNEL SELECTED Run stopped!
> STOP NO CHANNEL SELECTED". I don't the reasons. Can you help me ?
> The .out and .err files are presented in attachments. How to avoid
> these error later?
> Thank you very much!
>
> Hantao Jing
>
>
>

*$ 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)
      cosx = 0.0d0
      cosy = 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

* 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 -5.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
* BH1
  RPP BH1 -2500.00 2500.00 -2500.00 2500.00 -2500.00 2500.00
* C1
  RCC C1 0.00 10.00 0.00 0.00 -20.00 0.00
               55.00
* C2
  RCC C2 0.00 10.00 0.00 0.00 -20.00 0.00
               60.00
* C3
  RCC C3 0.00 10.00 0.00 0.00 -20.00 0.00
               65.00
* CC1
  RCC CC1 0.00 0.00 0.00 0.00 0.00 100.00
                6.77
* CC10
  RCC CC10 0.00 0.00 0.00 70.71 0.00 -70.71
                6.77
* CC11
  RCC CC11 0.00 0.00 0.00 50.00 0.00 -86.60
                6.77
* CC12
  RCC CC12 0.00 0.00 0.00 25.88 0.00 -96.59
                6.77
* CC13
  RCC CC13 0.00 0.00 0.00 0.00 0.00 -100.00
                6.77
* CC2
  RCC CC2 0.00 0.00 0.00 25.88 0.00 96.59
                6.77
* CC3
  RCC CC3 0.00 0.00 0.00 50.00 0.00 86.60
                6.77
* CC4
  RCC CC4 0.00 0.00 0.00 70.71 0.00 70.71
                6.77
* CC5
  RCC CC5 0.00 0.00 0.00 86.60 0.00 50.00
                6.77
* CC6
  RCC CC6 0.00 0.00 0.00 96.59 0.00 25.88
                6.77
* CC7
  RCC CC7 0.00 0.00 0.00 100.00 0.00 0.00
                6.77
* CC8
  RCC CC8 0.00 0.00 0.00 96.59 0.00 -25.88
                6.77
* CC9
  RCC CC9 0.00 0.00 0.00 86.60 0.00 -50.00
                6.77
* P1
  XYP P1 -15.00
* P2
  XYP P2 15.00
* TA
  RPP TA -3.00 3.00 -15.00 15.00 -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 - ( + ( +C3 -C1 ) + ( +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)
CDI1 5 + ( +CC1 -C1 ) +C2
* Reg # 7
* CDO1; assigned material: Vacuum; mat # (2)
CDO1 5 + ( +CC1 -C2 ) +C3
* Reg # 8
* CDI2; assigned material: Vacuum; mat # (2)
CDI2 5 + ( +CC2 -C1 ) +C2
* Reg # 9
* CDO2; assigned material: Vacuum; mat # (2)
CDO2 5 + ( +CC2 -C2 ) +C3
* Reg # 10
* CDI3; assigned material: Vacuum; mat # (2)
CDI3 5 + ( +CC3 -C1 ) +C2
* Reg # 11
* CDO3; assigned material: Vacuum; mat # (2)
CDO3 5 + ( +CC3 -C2 ) +C3
* Reg # 12
* CDI4; assigned material: Vacuum; mat # (2)
CDI4 5 + ( +CC4 -C1 ) +C2
* Reg # 13
* CDO4; assigned material: Vacuum; mat # (2)
CDO4 5 + ( +CC4 -C2 ) +C3
* Reg # 14
* CDI5; assigned material: Vacuum; mat # (2)
CDI5 5 + ( +CC5 -C1 ) +C2
* Reg # 15
* CDO5; assigned material: Vacuum; mat # (2)
CDO5 5 + ( +CC5 -C2 ) +C3
* Reg # 16
* CDI6; assigned material: Vacuum; mat # (2)
CDI6 5 + ( +CC6 -C1 ) +C2
* Reg # 17
* CDO6; assigned material: Vacuum; mat # (2)
CDO6 5 + ( +CC6 -C2 ) +C3
* Reg # 18
* CDI7; assigned material: Vacuum; mat # (2)
CDI7 5 + ( +CC7 -C1 ) +C2
* Reg # 19
* CDO7; assigned material: Vacuum; mat # (2)
CDO7 5 + ( +CC7 -C2 ) +C3
* Reg # 20
* CDI8; assigned material: Vacuum; mat # (2)
CDI8 5 + ( +CC8 -C1 ) +C2
* Reg # 21
* CDO8; assigned material: Vacuum; mat # (2)
CDO8 5 + ( +CC8 -C2 ) +C3
* Reg # 22
* CDI9; assigned material: Vacuum; mat # (2)
CDI9 5 + ( +CC9 -C1 ) +C2
* Reg # 23
* CDO9; assigned material: Vacuum; mat # (2)
CDO9 5 + ( +CC9 -C2 ) +C3
* Reg # 24
* CDI10; assigned material: Vacuum; mat # (2)
CDI10 5 + ( +CC10 -C1 ) +C2
* Reg # 25
* CDO10; assigned material: Vacuum; mat # (2)
CDO10 5 + ( +CC10 -C2 ) +C3
* Reg # 26
* CDI11; assigned material: Vacuum; mat # (2)
CDI11 5 + ( +CC11 -C1 ) +C2
* Reg # 27
* CDO11; assigned material: Vacuum; mat # (2)
CDO11 5 + ( +CC11 -C2 ) +C3
* Reg # 28
* CDI12; assigned material: Vacuum; mat # (2)
CDI12 5 + ( +CC12 -C1 ) +C2
* Reg # 29
* CDO12; assigned material: Vacuum; mat # (2)
CDO12 5 + ( +CC12 -C2 ) +C3
* Reg # 30
* CDI13; assigned material: Vacuum; mat # (2)
CDI13 5 + ( +CC13 -C1 ) +C2
* Reg # 31
* CDO13; assigned material: Vacuum; mat # (2)
CDO13 5 + ( +CC13 -C2 ) +C3
  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
*
*current from the target
*(4.1-3.9)/4.0 = 5%
* ..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
USRBDX -1.0 MUON+ -49.0 CDI1 CDO1 144.MUONs0
USRBDX 4.1E-3 3.9E-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.1E-3 3.9E-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.1E-3 3.9E-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.1E-3 3.9E-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.1E-3 3.9E-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.1E-3 3.9E-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.1E-3 3.9E-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.1E-3 3.9E-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.1E-3 3.9E-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.1E-3 3.9E-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.1E-3 3.9E-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.1E-3 3.9E-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.1E-3 3.9E-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.1E-3 3.9E-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.1E-3 3.9E-3 3.0 6.283185 0.0 1.0&
*
*
*
* ..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
RANDOMIZ 1.0 38088588.
* ..+....1....+....2....+....3....+....4....+....5....+....6....+....7....+....8
START 1.0E8
STOP

STOP STOP: FLUKA ABORTED statement executed
ownloading or receiving an authorized copy and/or using
  FLUKA, you agree with the following license/conditions/requests:

                Copyright statement and license conditions
    
  Copyright Italian National Institute for Nuclear Physics
  (INFN) and European Organization for Nuclear Research (CERN)
  ("the FLUKA copyright holders"), 1989-2009.
    
  All rights not expressly granted under this license are
  reserved.
    
  This software results from work performed by Alberto Fasso`,
  Alfredo Ferrari, Johannes Ranft and Paola Sala.
    
  INFN and CERN are the exclusive source of distribution of
  the code, bug fixes and documentation of the FLUKA
  software. Each official version of FLUKA is identified by a
  numbering scheme specifying major and minor releases.
    
  The FLUKA Coordination Committee or its delegates are able
  to grant any of the permissions noted in this License
  Agreement as requiring a specific consent. Any such consent
  may only be granted in writing.
    
  Installation, use, reproduction, display of the FLUKA
  software ("FLUKA"), in source and binary forms, are
  permitted free of charge on a non-exclusive basis for
  internal scientific, non-commercial and non-weapon-related
  use by non-profit organizations only. Any exercise of these
  rights is subject to the following conditions:
    
  1 Insertion of the FLUKA code, in whole or in part, into
    other codes, or its translation into any other computer
    language are possible only after obtaining prior written
    permission. Modifications of the FLUKA code are permitted
    for use by the licensee only, unless authorized in
    writing.
    
  2 FLUKA is non-transferable, non-sub-licensable and may not
    be distributed in any way, without express written
    consent, whether in original or modified form. Site-wise
    or collaboration-wise conditions can be agreed with the
    FLUKA Coordination Committee.
    
  3 Notwithstanding the above, the licensee may modify and
    sub-license FLUKA User Routines to third parties in so far
    as their purpose is limited to the adaptation of input and
    output interfaces of FLUKA and their modification does not
    circumvent, replace, add to or modify any of the functions
    of FLUKA, or extract specific isolated results from any of
    the individual internal physics models embedded within
    FLUKA.
    
  4 The licensee shall forthwith license all its modifications
    of FLUKA to the FLUKA copyright holders, at no cost and
    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.
    
  5 Any publication by the licensee with respect to FLUKA or
    results obtained from it shall explicitly acknowledge
    FLUKA by quoting its set of references and the FLUKA
    copyright holders. The licensee shall not without prior
    written permission publish documents or results based on a
    modified form of FLUKA, unless the modification
    exclusively concerns User Routines for the adaptation of
    its input and output interfaces which comply with the same
    restrictions, as defined in section 3) as those which
    apply to sub-licensing. Any publication of documents or
    results shall be based only on official FLUKA versions as
    obtained from the FLUKA website (http://www.fluka.org) or
    from any authorized mirror. Publication here implies any
    legal publication to any third party, whether verbal,
    electronic, visual, in writing or otherwise.
    
  6 The licensee shall ensure that the FLUKA references,
    copyright statement and license conditions are not altered
    or removed from FLUKA. Any integration of any portion of
    FLUKA, in modified or in unmodified form, into any other
    software package must preserve the internal copyright
    notices in those portions of FLUKA that have been
    employed, and must reproduce such notices within any
    additional global notices included along or embedded
    within the software into which FLUKA has been
    integrated. Any portion of FLUKA so integrated, whether
    modified or unmodified shall continue to be subject to
    these license conditions.
    
  7 Nothing in this license shall be construed as to grant any
    rights in any of the FLUKA versions since 1989. In
    addition, users are not permitted to circumvent any
    protection in prior distributions of FLUKA that provided
    for a preset expiration date of the code.
    
  8 Versions or parts of the FLUKA source code, entrusted to
    individuals or groups prior to the enactment of the
    CERN-INFN Collaboration Agreement, which are listed in
    Chapter 5 of Annex 1 of the EP-AB-INFN Scientific
    Agreement (19-02-2003), together with the agreed
    conditions of use, are subject to this License Agreement
    in addition to any other restrictions on the scope of use
    that may have been part of the initial use grant.
    
  9 Commercial use of FLUKA, outside the scope of this
    license, must be negotiated with the copyright holders.
    
  10 DISCLAIMER
    
  THIS SOFTWARE 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 THE SOFTWARE AND
  MODIFICATIONS THEREOF, WILL NOT INFRINGE ANY PATENT,
  COPYRIGHT, TRADE SECRET OR OTHER PROPRIETARY RIGHT.
    
  11 LIMITATION OF LIABILITY
    
  THE FLUKA COPYRIGHT HOLDERS AND THE AUTHORS SHALL HAVE NO
  LIABILITY FOR DIRECT, INDIRECT, SPECIAL, INCIDENTAL,
  CONSEQUENTIAL, EXEMPLARY, OR PUNITIVE 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
  THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH
  DAMAGES.
    
    
    
  REQUESTS MADE BY THE FLUKA AUTHORS TO ALL USERS
    
  All licensees are requested to report as soon as practical
  to the Authors any errors or bugs found in any portion of
  FLUKA and its accompanying documentation.
    
  All licensees are requested to forward copies of all
  comparisons that they make between FLUKA results and
  data or other codes as soon as practical. The Authors agree
  to keep any such communications confidential unless
  otherwise notified by the contributing user.
    
  The Authors reserve the right of publishing any benchmarking
  and/or comparisons of the distinct separate performance of
  the individual internal models that are embedded into FLUKA,
  whether the comparisons are with data or with other
  codes. The Authors would also like to convey a general
  willingness to conduct any such benchmarking efforts either
  upon request or in collaboration with interested parties. In
  case of doubt please contact the Authors.
    
  Users should exclusively download FLUKA from the official
  FLUKA website (http://www.fluka.org) or one of the
  authorized mirror sites. Users are invited to regularly
  update their FLUKA version to profit for improvements and
  bug fixes.
    
  Users are invited to use reasonably updated versions of the
  code for publications. Publications of results based on
  those FLUKA versions that are declared unsupported and
  obsolete on the official FLUKA website shall be avoided.
    
  Users should address any request of consent to one member of
  the FLUKA Coordinating Committee, which at present is
  composed as follows:
    
  Giuseppe Battistoni Giuseppe.Battistoni_at_mi.infn.it
  (chairman)
  Michael Doser Michael.Doser_at_cern.ch
  Roberto Losito Roberto.Losito_at_cern.ch
  Johannes Ranft Johannes.Ranft_at_cern.ch
  Paola Sala Paola.Sala_at_mi.infn.it
    

     In accordance with the User License, the use of the FLUKA code
     shall be acknowledged explicitly by quoting the following and
     only the following set of references:

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

   - G. Battistoni, S. Muraro, P.R. Sala, F. Cerutti, A. Ferrari,
     S. Roesler, A. Fasso`, J. Ranft
     "The FLUKA code: Description and benchmarking",
     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)

     !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     !!!! DOWNLOAD/USE OF THE FLUKA SOFTWARE IMPLIES FULL !!!!
     !!!! ACCEPTANCE OF THE LICENSE AND ASSOCIATED CONDITIONS !!!!
     !!!! INCLUDING THE AUTHOR'S REQUESTS !!!!
     !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

   Notes: The "FLUKA User Routines" mentioned at point 3) in the
          FLUKA User License are those (and only those) contained
          in the directory usermvax, both in the source and binary
          versions of the code

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

 Beam core parameters for inner and outer boundaries:
  0. 3.14000003
 Beam halo parameters for inner and outer boundaries:
  1.74065219 3.17413046
 STOP NO CHANNEL SELECTED

1 *====================================================================*
  * *
  * *
  * *
  * *
  * FFFFF L U U K K AAA 222 000 000 888 *
  * F L U U K K A A 2 2 0 0 0 0 8 8 *
  * F L U U K K A A 2 0 0 0 0 8 8 *
  * FFFF L U U KK AAAAA == 2 0 0 0 0 888 *
  * F L U U K K A A 2 0 0 0 0 8 8 *
  * F L U U K K A A 2 0 0 0 0 8 8 *
  * F LLLLL UUU K K A A 22222 000 000 888 *
  * *
  * *
  * *
  * Version of Fluka2008 for GNU/Linux operating system *
  * *
  * By : *
  * *
  * Alfredo Ferrari & Paola Sala INFN Milan & CERN/AB *
  * *
  * Alfredo.Ferrari_at_cern.ch Paola.Sala_at_mi.infn.it *
  * *
  * *
  * Alberto Fasso` SLAC, Stanford *
  * *
  * Fasso_at_slac.stanford.edu *
  * *
  * *
  * Johannes Ranft Siegen University *
  * *
  * Johannes.Ranft_at_cern.ch *
  * *
  * *
  * *
  * This version includes all the features of the Fluka2008 *
  * *
  * package *
  * *
  * *
  * *
  *====================================================================*

1

              FLUKA User license:

  By downloading or receiving an authorized copy and/or using
  FLUKA, you agree with the following license/conditions/requests:

                Copyright statement and license conditions
    
  Copyright Italian National Institute for Nuclear Physics
  (INFN) and European Organization for Nuclear Research (CERN)
  ("the FLUKA copyright holders"), 1989-2009.
    
  All rights not expressly granted under this license are
  reserved.
    
  This software results from work performed by Alberto Fasso`,
  Alfredo Ferrari, Johannes Ranft and Paola Sala.
    
  INFN and CERN are the exclusive source of distribution of
  the code, bug fixes and documentation of the FLUKA
  software. Each official version of FLUKA is identified by a
  numbering scheme specifying major and minor releases.
    
  The FLUKA Coordination Committee or its delegates are able
  to grant any of the permissions noted in this License
  Agreement as requiring a specific consent. Any such consent
  may only be granted in writing.
    
  Installation, use, reproduction, display of the FLUKA
  software ("FLUKA"), in source and binary forms, are
  permitted free of charge on a non-exclusive basis for
  internal scientific, non-commercial and non-weapon-related
  use by non-profit organizations only. Any exercise of these
  rights is subject to the following conditions:
    
  1 Insertion of the FLUKA code, in whole or in part, into
    other codes, or its translation into any other computer
    language are possible only after obtaining prior written
    permission. Modifications of the FLUKA code are permitted
    for use by the licensee only, unless authorized in
    writing.
    
  2 FLUKA is non-transferable, non-sub-licensable and may not
    be distributed in any way, without express written
    consent, whether in original or modified form. Site-wise
    or collaboration-wise conditions can be agreed with the
    FLUKA Coordination Committee.
    
  3 Notwithstanding the above, the licensee may modify and
    sub-license FLUKA User Routines to third parties in so far
    as their purpose is limited to the adaptation of input and
    output interfaces of FLUKA and their modification does not
    circumvent, replace, add to or modify any of the functions
    of FLUKA, or extract specific isolated results from any of
    the individual internal physics models embedded within
    FLUKA.
    
  4 The licensee shall forthwith license all its modifications
    of FLUKA to the FLUKA copyright holders, at no cost and
    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.
    
  5 Any publication by the licensee with respect to FLUKA or
    results obtained from it shall explicitly acknowledge
    FLUKA by quoting its set of references and the FLUKA
    copyright holders. The licensee shall not without prior
    written permission publish documents or results based on a
    modified form of FLUKA, unless the modification
    exclusively concerns User Routines for the adaptation of
    its input and output interfaces which comply with the same
    restrictions, as defined in section 3) as those which
    apply to sub-licensing. Any publication of documents or
    results shall be based only on official FLUKA versions as
    obtained from the FLUKA website (http://www.fluka.org) or
    from any authorized mirror. Publication here implies any
    legal publication to any third party, whether verbal,
    electronic, visual, in writing or otherwise.
    
  6 The licensee shall ensure that the FLUKA references,
    copyright statement and license conditions are not altered
    or removed from FLUKA. Any integration of any portion of
    FLUKA, in modified or in unmodified form, into any other
    software package must preserve the internal copyright
    notices in those portions of FLUKA that have been
    employed, and must reproduce such notices within any
    additional global notices included along or embedded
    within the software into which FLUKA has been
    integrated. Any portion of FLUKA so integrated, whether
    modified or unmodified shall continue to be subject to
    these license conditions.
    
  7 Nothing in this license shall be construed as to grant any
    rights in any of the FLUKA versions since 1989. In
    addition, users are not permitted to circumvent any
    protection in prior distributions of FLUKA that provided
    for a preset expiration date of the code.
    
  8 Versions or parts of the FLUKA source code, entrusted to
    individuals or groups prior to the enactment of the
    CERN-INFN Collaboration Agreement, which are listed in
    Chapter 5 of Annex 1 of the EP-AB-INFN Scientific
    Agreement (19-02-2003), together with the agreed
    conditions of use, are subject to this License Agreement
    in addition to any other restrictions on the scope of use
    that may have been part of the initial use grant.
    
  9 Commercial use of FLUKA, outside the scope of this
    license, must be negotiated with the copyright holders.
    
  10 DISCLAIMER
    
  THIS SOFTWARE 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 THE SOFTWARE AND
  MODIFICATIONS THEREOF, WILL NOT INFRINGE ANY PATENT,
  COPYRIGHT, TRADE SECRET OR OTHER PROPRIETARY RIGHT.
    
  11 LIMITATION OF LIABILITY
    
  THE FLUKA COPYRIGHT HOLDERS AND THE AUTHORS SHALL HAVE NO
  LIABILITY FOR DIRECT, INDIRECT, SPECIAL, INCIDENTAL,
  CONSEQUENTIAL, EXEMPLARY, OR PUNITIVE 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
  THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH
  DAMAGES.
    
    
    
  REQUESTS MADE BY THE FLUKA AUTHORS TO ALL USERS
    
  All licensees are requested to report as soon as practical
  to the Authors any errors or bugs found in any portion of
  FLUKA and its accompanying documentation.
    
  All licensees are requested to forward copies of all
  comparisons that they make between FLUKA results and
  data or other codes as soon as practical. The Authors agree
  to keep any such communications confidential unless
  otherwise notified by the contributing user.
    
  The Authors reserve the right of publishing any benchmarking
  and/or comparisons of the distinct separate performance of
  the individual internal models that are embedded into FLUKA,
  whether the comparisons are with data or with other
  codes. The Authors would also like to convey a general
  willingness to conduct any such benchmarking efforts either
  upon request or in collaboration with interested parties. In
  case of doubt please contact the Authors.
    
  Users should exclusively download FLUKA from the official
  FLUKA website (http://www.fluka.org) or one of the
  authorized mirror sites. Users are invited to regularly
  update their FLUKA version to profit for improvements and
  bug fixes.
    
  Users are invited to use reasonably updated versions of the
  code for publications. Publications of results based on
  those FLUKA versions that are declared unsupported and
  obsolete on the official FLUKA website shall be avoided.
    
  Users should address any request of consent to one member of
  the FLUKA Coordinating Committee, which at present is
  composed as follows:
    
  Giuseppe Battistoni Giuseppe.Battistoni_at_mi.infn.it
  (chairman)
  Michael Doser Michael.Doser_at_cern.ch
  Roberto Losito Roberto.Losito_at_cern.ch
  Johannes Ranft Johannes.Ranft_at_cern.ch
  Paola Sala Paola.Sala_at_mi.infn.it
    

     In accordance with the User License, the use of the FLUKA code
     shall be acknowledged explicitly by quoting the following and
     only the following set of references:

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

   - G. Battistoni, S. Muraro, P.R. Sala, F. Cerutti, A. Ferrari,
     S. Roesler, A. Fasso`, J. Ranft
     "The FLUKA code: Description and benchmarking",
     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)

     !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     !!!! DOWNLOAD/USE OF THE FLUKA SOFTWARE IMPLIES FULL !!!!
     !!!! ACCEPTANCE OF THE LICENSE AND ASSOCIATED CONDITIONS !!!!
     !!!! INCLUDING THE AUTHOR'S REQUESTS !!!!
     !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

   Notes: The "FLUKA User Routines" mentioned at point 3) in the
          FLUKA User License are those (and only those) contained
          in the directory usermvax, both in the source and binary
          versions of the code

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

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

   FLUKA2008 Version 3b.2 Oct-09 by A. Ferrari DATE: 5/13/10 TIME: 22:33:30

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

 *---------------- 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 ----------------*
 *---------------- ----------------*
 *---------------- current from the target ----------------*
 *---------------- (4.1-3.9)/4.0 = 5% ----------------*
 *---------------- ..+....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 -5.000 0.000 0.000 0.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 ***** GEOBEGIN 0.000 0.000 0.000 0.000 0.000 0.000

1

          MC-CAD

                    IVOPT = 0 IDBG = 0

                                                  Body data
 *
 *--------------- BH1 ---------------*
 *
 *
 *--------------- C1 ---------------*
 *
  RPP BH1 1 -0.25000000E+04 0.25000000E+04 -0.25000000E+04 0.25000000E+04 -0.25000000E+04 0.25000000E+04 5
 *
 *--------------- C2 ---------------*
 *
  RCC C1 2 0.00000000E+00 0.10000000E+02 0.00000000E+00 0.00000000E+00 -0.20000000E+02 0.00000000E+00 15
                          0.55000000E+02
 *
 *--------------- C3 ---------------*
 *
  RCC C2 3 0.00000000E+00 0.10000000E+02 0.00000000E+00 0.00000000E+00 -0.20000000E+02 0.00000000E+00 26
                          0.60000000E+02
 *
 *--------------- CC1 ---------------*
 *
  RCC C3 4 0.00000000E+00 0.10000000E+02 0.00000000E+00 0.00000000E+00 -0.20000000E+02 0.00000000E+00 37
                          0.65000000E+02
 *
 *--------------- CC10 ---------------*
 *
  RCC CC1 5 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.10000000E+03 48
                          0.67700000E+01
 *
 *--------------- CC11 ---------------*
 *
  RCC CC10 6 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.70710000E+02 0.00000000E+00 -0.70710000E+02 59
                          0.67700000E+01
 *
 *--------------- CC12 ---------------*
 *
  RCC CC11 7 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.50000000E+02 0.00000000E+00 -0.86600000E+02 70
                          0.67700000E+01
 *
 *--------------- CC13 ---------------*
 *
  RCC CC12 8 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.25880000E+02 0.00000000E+00 -0.96590000E+02 81
                          0.67700000E+01
 *
 *--------------- CC2 ---------------*
 *
  RCC CC13 9 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.00000000E+00 -0.10000000E+03 92
                          0.67700000E+01
 *
 *--------------- CC3 ---------------*
 *
  RCC CC2 10 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.25880000E+02 0.00000000E+00 0.96590000E+02 103
                          0.67700000E+01
 *
 *--------------- CC4 ---------------*
 *
  RCC CC3 11 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.50000000E+02 0.00000000E+00 0.86600000E+02 114
                          0.67700000E+01
 *
 *--------------- CC5 ---------------*
 *
  RCC CC4 12 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.70710000E+02 0.00000000E+00 0.70710000E+02 125
                          0.67700000E+01
 *
 *--------------- CC6 ---------------*
 *
  RCC CC5 13 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.86600000E+02 0.00000000E+00 0.50000000E+02 136
                          0.67700000E+01
 *
 *--------------- CC7 ---------------*
 *
  RCC CC6 14 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.96590000E+02 0.00000000E+00 0.25880000E+02 147
                          0.67700000E+01
 *
 *--------------- CC8 ---------------*
 *
  RCC CC7 15 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.10000000E+03 0.00000000E+00 0.00000000E+00 158
                          0.67700000E+01
 *
 *--------------- CC9 ---------------*
 *
  RCC CC8 16 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.96590000E+02 0.00000000E+00 -0.25880000E+02 169
                          0.67700000E+01
 *
 *--------------- P1 ---------------*
 *
  RCC CC9 17 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.86600000E+02 0.00000000E+00 -0.50000000E+02 180
                          0.67700000E+01
 *
 *--------------- P2 ---------------*
 *
  XYP P1 18 -0.15000000E+02 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.00000000E+00 191
 *
 *--------------- TA ---------------*
 *
  XYP P2 19 0.15000000E+02 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.00000000E+00 201
 *
 *--------------- VA1 ---------------*
 *
  RPP TA 20 -0.30000000E+01 0.30000000E+01 -0.15000000E+02 0.15000000E+02 -0.20000000E+02 0.20000000E+02 211
  RPP VA1 21 -0.20000000E+04 0.20000000E+04 -0.20000000E+04 0.20000000E+04 -0.20000000E+04 0.20000000E+04 221
  END 22 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.00000000E+00 0.00000000E+00 231
 Number of bodies 21
 Length of FPD-Array 236

                                                  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 - C3 - TA
| + C1 + VA1 - TA | +
VA1 - CC1 - CC10 - CC11 - CC12
- CC13 - CC2 - CC3 - CC4 -
CC5 - CC6 - CC7 - CC8 - CC9
- TA
 *
 *--------------- 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) ---------------*
 *
CDI1 5 + C2 + CC1 - C1
 *
 *--------------- Reg # 7 ---------------*
 *
 *
 *--------------- CDO1; assigned material: Vacuum; mat # (2) ---------------*
 *
CDO1 5 + C3 + CC1 - C2
 *
 *--------------- Reg # 8 ---------------*
 *
 *
 *--------------- CDI2; assigned material: Vacuum; mat # (2) ---------------*
 *
CDI2 5 + C2 + CC2 - C1
 *
 *--------------- Reg # 9 ---------------*
 *
 *
 *--------------- CDO2; assigned material: Vacuum; mat # (2) ---------------*
 *
CDO2 5 + C3 + CC2 - C2
 *
 *--------------- Reg # 10 ---------------*
 *
 *
 *--------------- CDI3; assigned material: Vacuum; mat # (2) ---------------*
 *
CDI3 5 + C2 + CC3 - C1
 *
 *--------------- Reg # 11 ---------------*
 *
 *
 *--------------- CDO3; assigned material: Vacuum; mat # (2) ---------------*
 *
CDO3 5 + C3 + CC3 - C2
 *
 *--------------- Reg # 12 ---------------*
 *
 *
 *--------------- CDI4; assigned material: Vacuum; mat # (2) ---------------*
 *
CDI4 5 + C2 + CC4 - C1
 *
 *--------------- Reg # 13 ---------------*
 *
 *
 *--------------- CDO4; assigned material: Vacuum; mat # (2) ---------------*
 *
CDO4 5 + C3 + CC4 - C2
 *
 *--------------- Reg # 14 ---------------*
 *
 *
 *--------------- CDI5; assigned material: Vacuum; mat # (2) ---------------*
 *
CDI5 5 + C2 + CC5 - C1
 *
 *--------------- Reg # 15 ---------------*
 *
 *
 *--------------- CDO5; assigned material: Vacuum; mat # (2) ---------------*
 *
CDO5 5 + C3 + CC5 - C2
 *
 *--------------- Reg # 16 ---------------*
 *
 *
 *--------------- CDI6; assigned material: Vacuum; mat # (2) ---------------*
 *
CDI6 5 + C2 + CC6 - C1
 *
 *--------------- Reg # 17 ---------------*
 *
 *
 *--------------- CDO6; assigned material: Vacuum; mat # (2) ---------------*
 *
CDO6 5 + C3 + CC6 - C2
 *
 *--------------- Reg # 18 ---------------*
 *
 *
 *--------------- CDI7; assigned material: Vacuum; mat # (2) ---------------*
 *
CDI7 5 + C2 + CC7 - C1
 *
 *--------------- Reg # 19 ---------------*
 *
 *
 *--------------- CDO7; assigned material: Vacuum; mat # (2) ---------------*
 *
CDO7 5 + C3 + CC7 - C2
 *
 *--------------- Reg # 20 ---------------*
 *
 *
 *--------------- CDI8; assigned material: Vacuum; mat # (2) ---------------*
 *
CDI8 5 + C2 + CC8 - C1
 *
 *--------------- Reg # 21 ---------------*
 *
 *
 *--------------- CDO8; assigned material: Vacuum; mat # (2) ---------------*
 *
CDO8 5 + C3 + CC8 - C2
 *
 *--------------- Reg # 22 ---------------*
 *
 *
 *--------------- CDI9; assigned material: Vacuum; mat # (2) ---------------*
 *
CDI9 5 + C2 + CC9 - C1
 *
 *--------------- Reg # 23 ---------------*
 *
 *
 *--------------- CDO9; assigned material: Vacuum; mat # (2) ---------------*
 *
CDO9 5 + C3 + CC9 - C2
 *
 *--------------- Reg # 24 ---------------*
 *
 *
 *--------------- CDI10; assigned material: Vacuum; mat # (2) ---------------*
 *
CDI10 5 + C2 + CC10 - C1
 *
 *--------------- Reg # 25 ---------------*
 *
 *
 *--------------- CDO10; assigned material: Vacuum; mat # (2) ---------------*
 *
CDO10 5 + C3 + CC10 - C2
 *
 *--------------- Reg # 26 ---------------*
 *
 *
 *--------------- CDI11; assigned material: Vacuum; mat # (2) ---------------*
 *
CDI11 5 + C2 + CC11 - C1
 *
 *--------------- Reg # 27 ---------------*
 *
 *
 *--------------- CDO11; assigned material: Vacuum; mat # (2) ---------------*
 *
CDO11 5 + C3 + CC11 - C2
 *
 *--------------- Reg # 28 ---------------*
 *
 *
 *--------------- CDI12; assigned material: Vacuum; mat # (2) ---------------*
 *
CDI12 5 + C2 + CC12 - C1
 *
 *--------------- Reg # 29 ---------------*
 *
 *
 *--------------- CDO12; assigned material: Vacuum; mat # (2) ---------------*
 *
CDO12 5 + C3 + CC12 - C2
 *
 *--------------- Reg # 30 ---------------*
 *
 *
 *--------------- CDI13; assigned material: Vacuum; mat # (2) ---------------*
 *
CDI13 5 + C2 + CC13 - C1
 *
 *--------------- Reg # 31 ---------------*
 *
 *
 *--------------- CDO13; assigned material: Vacuum; mat # (2) ---------------*
 *
CDO13 5 + C3 + CC13 - C2
  END
 Number of input regions 31
 Number of code zones 33
 Length of integer array 923

 CODE ZONE INPUT REGION ZONE DATA LOC. NO. OF BODIES REGION NO.
      1 1 148 2 1
      2 2 157 3 2
      3 2 170 3 2
      4 2 183 15 2
      5 3 244 2 3
      6 4 253 3 4
      7 5 266 2 5
      8 6 275 3 6
      9 7 288 3 7
     10 8 301 3 8
     11 9 314 3 9
     12 10 327 3 10
     13 11 340 3 11
     14 12 353 3 12
     15 13 366 3 13
     16 14 379 3 14
     17 15 392 3 15
     18 16 405 3 16
     19 17 418 3 17
     20 18 431 3 18
     21 19 444 3 19
     22 20 457 3 20
     23 21 470 3 21
     24 22 483 3 22
     25 23 496 3 23
     26 24 509 3 24
     27 25 522 3 25
     28 26 535 3 26
     29 27 548 3 27
     30 28 561 3 28
     31 29 574 3 29
     32 30 587 3 30
     33 31 600 3 31

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

 Interpreted body echo

 Body n. 1 RPP BH1
         -2500.000 2500.000 -2500.000 2500.000 -2500.000 2500.000
 Body n. 2 RCC C1
          0.000000 10.00000 0.000000 0.000000 -20.00000 0.000000
          55.00000
 Body n. 3 RCC C2
          0.000000 10.00000 0.000000 0.000000 -20.00000 0.000000
          60.00000
 Body n. 4 RCC C3
          0.000000 10.00000 0.000000 0.000000 -20.00000 0.000000
          65.00000
 Body n. 5 RCC CC1
          0.000000 0.000000 0.000000 0.000000 0.000000 100.0000
          6.770000
 Body n. 6 RCC CC10
          0.000000 0.000000 0.000000 70.71000 0.000000 -70.71000
          6.770000
 Body n. 7 RCC CC11
          0.000000 0.000000 0.000000 50.00000 0.000000 -86.60000
          6.770000
 Body n. 8 RCC CC12
          0.000000 0.000000 0.000000 25.88000 0.000000 -96.59000
          6.770000
 Body n. 9 RCC CC13
          0.000000 0.000000 0.000000 0.000000 0.000000 -100.0000
          6.770000
 Body n. 10 RCC CC2
          0.000000 0.000000 0.000000 25.88000 0.000000 96.59000
          6.770000
 Body n. 11 RCC CC3
          0.000000 0.000000 0.000000 50.00000 0.000000 86.60000
          6.770000
 Body n. 12 RCC CC4
          0.000000 0.000000 0.000000 70.71000 0.000000 70.71000
          6.770000
 Body n. 13 RCC CC5
          0.000000 0.000000 0.000000 86.60000 0.000000 50.00000
          6.770000
 Body n. 14 RCC CC6
          0.000000 0.000000 0.000000 96.59000 0.000000 25.88000
          6.770000
 Body n. 15 RCC CC7
          0.000000 0.000000 0.000000 100.0000 0.000000 0.000000
          6.770000
 Body n. 16 RCC CC8
          0.000000 0.000000 0.000000 96.59000 0.000000 -25.88000
          6.770000
 Body n. 17 RCC CC9
          0.000000 0.000000 0.000000 86.60000 0.000000 -50.00000
          6.770000
 Body n. 18 XYP P1
         -15.00000
 Body n. 19 XYP P2
          15.00000
 Body n. 20 RPP TA
         -3.000000 3.000000 -15.00000 15.00000 -20.00000 20.00000
 Body n. 21 RPP VA1
         -2000.000 2000.000 -2000.000 2000.000 -2000.000 2000.000

 Interpreted region echo

 Region n. 1 BH
                  1 -21
 Region n. 2 VA
          OR 21 -4 -20
          OR 2 21 -20
          OR 21 -5 -6 -7 -8 -9 -10
                -11 -12 -13 -14 -15 -16 -17
                -20
 Region n. 3 TA1
                 20 18
 Region n. 4 TA2
                 19 20 -18
 Region n. 5 DE1
                 20 -19
 Region n. 6 CDI1
                  3 5 -2
 Region n. 7 CDO1
                  4 5 -3
 Region n. 8 CDI2
                  3 10 -2
 Region n. 9 CDO2
                  4 10 -3
 Region n. 10 CDI3
                  3 11 -2
 Region n. 11 CDO3
                  4 11 -3
 Region n. 12 CDI4
                  3 12 -2
 Region n. 13 CDO4
                  4 12 -3
 Region n. 14 CDI5
                  3 13 -2
 Region n. 15 CDO5
                  4 13 -3
 Region n. 16 CDI6
                  3 14 -2
 Region n. 17 CDO6
                  4 14 -3
 Region n. 18 CDI7
                  3 15 -2
 Region n. 19 CDO7
                  4 15 -3
 Region n. 20 CDI8
                  3 16 -2
 Region n. 21 CDO8
                  4 16 -3
 Region n. 22 CDI9
                  3 17 -2
 Region n. 23 CDO9
                  4 17 -3
 Region n. 24 CDI10
                  3 6 -2
 Region n. 25 CDO10
                  4 6 -3
 Region n. 26 CDI11
                  3 7 -2
 Region n. 27 CDO11
                  4 7 -3
 Region n. 28 CDI12
                  3 8 -2
 Region n. 29 CDO12
                  4 8 -3
 Region n. 30 CDI13
                  3 9 -2
 Region n. 31 CDO13
                  4 9 -3
1 OPTION 0 WAS USED IN CALCULATING VOLUMES, FOR 31 REGIONS
 3: INPUT VOLUMES, ANYTHING ELSE: VOLUMES = 1.0
 

           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

1 REG 11 12 13 14 15 16 17 18 19 20
 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

1 REG 21 22 23 24 25 26 27 28 29 30
 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

1 REG 31
 VOLUME 1.000E+00
  *** Region # 2 Dnear according to possible overlapping ORs ***
0NGEOM= 4002, NGLAST= 5940

 **** Stars/Energy accumulation arrays start at location 5943 and end at 6190 (I*4 addr.) ****
GEOEND

 Total time used for geometry initialization: 0.116 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 3.8089E+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 88588 380 38088588

 ***** 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 ***** USRBDX -1.000 10.00 -49.00 6.000 7.000 144.0 MUONs0

 ***** Next control card ***** USRBDX 4.1000E-03 3.9000E-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.1000E-03 3.9000E-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.1000E-03 3.9000E-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.1000E-03 3.9000E-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.1000E-03 3.9000E-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.1000E-03 3.9000E-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.1000E-03 3.9000E-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.1000E-03 3.9000E-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.1000E-03 3.9000E-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.1000E-03 3.9000E-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.1000E-03 3.9000E-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.1000E-03 3.9000E-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.1000E-03 3.9000E-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.1000E-03 3.9000E-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.1000E-03 3.9000E-03 3.000 6.283 0.000 1.000 &

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

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

  *** Reading evaporation and nuclear data from unit: 14
  *** Evaporation: using NNDC (1996) data ***

 Starting location in blank common of LVL data: 6192
 Last location in blank common of LVL data: 588661

 Starting location in blank common of CE data: 588662
 Last location in blank common of CE data: 639463

 Starting location in blank common of alpha data: 639464
 Last location in blank common of alpha data: 642225

 Starting location in blank common of gamma data: 642226
 Last location in blank common of gamma data: 773303

 Starting location in blank common of beta data: 773304
 Last location in blank common of beta data: 815642

 Starting location in blank common of GDR data: 815643
 Last location in blank common of GDR data: 870697

 Starting location in blank common of (g,x) data: 870698
 Last location in blank common of (g,x) data: 1173360

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

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

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

  **** 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.: 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 1173361 and end at 1175854 (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 1175857 and end at 1175918 (I*4 addr.) ****

 **** Biased downscattering factors start at location 1175921 and end at 1175982 (I*4 addr.) ****

 **** Non analog absorption group limits start at location 1175983 and end at 1176013 (I*4 addr.) ****

 **** Biased downscattering group limits start at location 1176014 and end at 1176044 (I*4 addr.) ****

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

 **** Lower Weight Window limits start at location 1176077 and end at 1176138 (I*4 addr.) ****
1
 ***** Neutron Xsec: group limits, average energies, velocities and momenta *****
 ***** start at location 1176139, end at location 1178306 (I*4 addr.) *****

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

 Group cross sections storage starts at 1180127
 Last location used for group xsecs 1343429

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

   **** 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 1343433 *****
 ***** end at location 1346960 (I*4 addresses) *****

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

 ***** Range tabulations in blank common start at location 1346963 *****
 ***** end at location 1347070 (I*4 addresses) *****

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

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

 ***** Xsec tabulations in blank common start at location 1347073 *****
 ***** end at location 1354010 (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 1347073 *****
 ***** end at location 1354010 (I*4 addresses) *****

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

 *** Blank common cells from 1415383 to 1415603 allocated for an EMF R*4 tab. array

 *** Blank common cells from 1415604 to 1415895 allocated for an EMF R*4 tab. array

 *** Blank common cells from 1415896 to 1416204 allocated for an EMF R*4 tab. array

 *** Blank common cells from 1416205 to 1416513 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)

 *** Blank common cells from 1421377 to 1422000 allocated for an EMF tab. array

 *** Blank common cells from 1422001 to 1422624 allocated for an EMF tab. array

 *** Blank common cells from 1422625 to 1423248 allocated for an EMF tab. array

 *** Blank common cells from 1423249 to 1423872 allocated for an EMF tab. array

 *** Blank common cells from 1423873 to 1424496 allocated for an EMF tab. array

 *** Blank common cells from 1424497 to 1425120 allocated for an EMF tab. array

 *** Blank common cells from 1425121 to 1425744 allocated for an EMF tab. array

 *** Blank common cells from 1425745 to 1426368 allocated for an EMF tab. array

 *** Blank common cells from 1426369 to 1426992 allocated for an EMF tab. array

 *** Blank common cells from 1426993 to 1427616 allocated for an EMF tab. array

 *** Blank common cells from 1427617 to 1428240 allocated for an EMF tab. array

 *** Blank common cells from 1428241 to 1428864 allocated for an EMF tab. array

 *** Blank common cells from 1428865 to 1429488 allocated for an EMF tab. array

 *** Blank common cells from 1429489 to 1430518 allocated for an EMF tab. array

 *** Blank common cells from 1430519 to 1431548 allocated for an EMF tab. array

 *** Blank common cells from 1431549 to 1432578 allocated for an EMF tab. array

 *** Blank common cells from 1432579 to 1433608 allocated for an EMF tab. array

 *** Blank common cells from 1433609 to 1434638 allocated for an EMF tab. array

 *** Blank common cells from 1434639 to 1435668 allocated for an EMF tab. array

 *** Blank common cells from 1435669 to 1436698 allocated for an EMF tab. array

 ***** EMF tabulations in blank common start at location 1416514 *****
 ***** end at location 1436698 (I*4 addresses) *****

 *** Blank common cells from 1436699 to 1437322 allocated for an EMF tab. array

 *** Blank common cells from 1437323 to 1437946 allocated for an EMF tab. array
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
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
          2 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
          3 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
          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
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
          6 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
          7 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
          8 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
          9 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         10 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         11 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         12 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         13 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         14 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         15 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         16 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         17 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         18 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         19 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         20 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         21 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         22 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         23 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         24 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         25 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         26 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         27 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         28 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         29 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         30 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F
         31 0 VACUUM 2 VACUUM
     Ecut = 0.0000E+00 MeV, Pcut = 0.0000E+00 MeV, BIAS = F, Ray. = F, S(q,Z) = T, Pz(q,Z) = F

 Starting location in blank common of bdrx data: 1437949
 Last location in blank common of bdrx data: 1438041
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
 BLANK 241
 BLANK 242
 BLANK 243
 BLANK 244
 BLANK 245
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 -5.00000000 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)
    The nominal beam position belongs to region: 4(TA2 ), 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 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

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

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

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

   Cut-off kinetic energy for DEUTERON transport: 1.999E-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 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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. 2 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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 "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.9000E-03 to 4.1000E-03 GeV, 3 bins (ratio : 1.0168E+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)
                                                Minimum and Maximum step size (cm)
     1 BH 1 BLCKHOLE OFF 0.00000E+00 9.99852E+04
     2 VA 2 VACUUM OFF 0.00000E+00 9.99852E+04
     3 TA1 2 VACUUM OFF 0.00000E+00 9.99852E+04
     4 TA2 6 CARBON OFF 0.00000E+00 9.99852E+04
     5 DE1 2 VACUUM OFF 0.00000E+00 9.99852E+04
     6 CDI1 2 VACUUM OFF 0.00000E+00 9.99852E+04
     7 CDO1 2 VACUUM OFF 0.00000E+00 9.99852E+04
     8 CDI2 2 VACUUM OFF 0.00000E+00 9.99852E+04
     9 CDO2 2 VACUUM OFF 0.00000E+00 9.99852E+04
    10 CDI3 2 VACUUM OFF 0.00000E+00 9.99852E+04
    11 CDO3 2 VACUUM OFF 0.00000E+00 9.99852E+04
    12 CDI4 2 VACUUM OFF 0.00000E+00 9.99852E+04
    13 CDO4 2 VACUUM OFF 0.00000E+00 9.99852E+04
    14 CDI5 2 VACUUM OFF 0.00000E+00 9.99852E+04
    15 CDO5 2 VACUUM OFF 0.00000E+00 9.99852E+04
    16 CDI6 2 VACUUM OFF 0.00000E+00 9.99852E+04
    17 CDO6 2 VACUUM OFF 0.00000E+00 9.99852E+04
    18 CDI7 2 VACUUM OFF 0.00000E+00 9.99852E+04
    19 CDO7 2 VACUUM OFF 0.00000E+00 9.99852E+04
    20 CDI8 2 VACUUM OFF 0.00000E+00 9.99852E+04
    21 CDO8 2 VACUUM OFF 0.00000E+00 9.99852E+04
    22 CDI9 2 VACUUM OFF 0.00000E+00 9.99852E+04
    23 CDO9 2 VACUUM OFF 0.00000E+00 9.99852E+04
    24 CDI10 2 VACUUM OFF 0.00000E+00 9.99852E+04
    25 CDO10 2 VACUUM OFF 0.00000E+00 9.99852E+04
    26 CDI11 2 VACUUM OFF 0.00000E+00 9.99852E+04
    27 CDO11 2 VACUUM OFF 0.00000E+00 9.99852E+04
    28 CDI12 2 VACUUM OFF 0.00000E+00 9.99852E+04
    29 CDO12 2 VACUUM OFF 0.00000E+00 9.99852E+04
    30 CDI13 2 VACUUM OFF 0.00000E+00 9.99852E+04
    31 CDO13 2 VACUUM OFF 0.00000E+00 9.99852E+04

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

 Total time used for initialization: 0.638 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 15A0C 17C 0 0
          1 99999999 99999999 0.0000000E+00 1.0000000E+30 0
 NEXT SEEDS: 27 0 0 0 0 0 15A0C 17C 0 0
  *** Frmbrk: we are dealing with a bag of 7 46.4179611
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 108.62043
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 116.558746
  identical nucleons, go on folks! ***
    2000000 98000000 98000000 4.8552568E-04 1.0000000E+30 1406284
 NEXT SEEDS:1183E815 3 0 0 0 0 15A0C 17C 0 0
    4000000 96000000 96000000 4.8532873E-04 1.0000000E+30 2811178
 NEXT SEEDS:22C53773 6 0 0 0 0 15A0C 17C 0 0
  *** Frmbrk: we are dealing with a bag of 7 104.804054
  identical nucleons, go on folks! ***
    6000000 94000000 94000000 4.8514341E-04 1.0000000E+30 4213885
 NEXT SEEDS:33E1EC11 9 0 0 0 0 15A0C 17C 0 0
  *** Frmbrk: we are dealing with a bag of 7 86.3225708
  identical nucleons, go on folks! ***
    8000000 92000000 92000000 4.8511949E-04 1.0000000E+30 5617898
 NEXT SEEDS: 978F6E2 D 0 0 0 0 15A0C 17C 0 0
  *** Frmbrk: we are dealing with a bag of 7 77.3935089
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 56.7081833
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 60.151577
  identical nucleons, go on folks! ***
  *** Umfadj_sng: Umo, Amcms(1)+Amcms(nttprt), Amcms(1) 11.3170051 11.3188759
  0.13956995 ***
   10000000 90000000 90000000 4.8507035E-04 1.0000000E+30 7021533
 NEXT SEEDS:1A8BFEA3 10 0 0 0 0 15A0C 17C 0 0
  *** Umfadj_sng: Umo, Amcms(1)+Amcms(nttprt), Amcms(1) 11.3187525 11.3188759
  0.13956995 ***
  *** Frmbrk: we are dealing with a bag of 7 41.2751427
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 81.8596191
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 40.0459633
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 87.6314087
  identical nucleons, go on folks! ***
   12000000 88000000 88000000 4.8506407E-04 1.0000000E+30 8426774
 NEXT SEEDS:2BB9704E 13 0 0 0 0 15A0C 17C 0 0
  *** Frmbrk: we are dealing with a bag of 7 43.7186089
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 123.008759
  identical nucleons, go on folks! ***
   14000000 86000000 86000000 4.8492765E-04 1.0000000E+30 9830060
 NEXT SEEDS: DEF744 17 0 0 0 0 15A0C 17C 0 0
  *** Frmbrk: we are dealing with a bag of 7 51.4035072
  identical nucleons, go on folks! ***
   16000000 84000000 84000000 4.8486803E-04 1.0000000E+30 11235541
 NEXT SEEDS:11C5E6D5 1A 0 0 0 0 15A0C 17C 0 0
  *** Frmbrk: we are dealing with a bag of 7 83.5386581
  identical nucleons, go on folks! ***
   18000000 82000000 82000000 4.8496812E-04 1.0000000E+30 12642296
 NEXT SEEDS:2362B8B2 1D 0 0 0 0 15A0C 17C 0 0
  *** Frmbrk: we are dealing with a bag of 7 77.5081635
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 60.9322395
  identical nucleons, go on folks! ***
   20000000 80000000 80000000 4.8491095E-04 1.0000000E+30 14045897
 NEXT SEEDS:343752D8 20 0 0 0 0 15A0C 17C 0 0
  *** Frmbrk: we are dealing with a bag of 7 70.8332214
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 58.258728
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 98.4417648
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 56.1487617
  identical nucleons, go on folks! ***
   22000000 78000000 78000000 4.8488132E-04 1.0000000E+30 15449840
 NEXT SEEDS: 9867ECC 24 0 0 0 0 15A0C 17C 0 0
  *** Frmbrk: we are dealing with a bag of 7 164.510681
  identical nucleons, go on folks! ***
   24000000 76000000 76000000 4.8486403E-04 1.0000000E+30 16854466
 NEXT SEEDS:1A84B72E 27 0 0 0 0 15A0C 17C 0 0
  *** Frmbrk: we are dealing with a bag of 7 90.3398514
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 73.0349045
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 70.722229
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 139.653839
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 60.5345001
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 118.646873
  identical nucleons, go on folks! ***
  *** Frmbrk: we are dealing with a bag of 7 43.7355232
  identical nucleons, go on folks! ***
   26000000 74000000 74000000 4.8486070E-04 1.0000000E+30 18258640
 NEXT SEEDS:2BA52DC6 2A 0 0 0 0 15A0C 17C 0 0
  *** Frmbrk: we are dealing with a bag of 7 80.7054825
  identical nucleons, go on folks! ***
   28000000 72000000 72000000 4.8484160E-04 1.0000000E+30 19661562
 NEXT SEEDS: 1038F27 2E 0 0 0 0 15A0C 17C 0 0
  *** Frmbrk: we are dealing with a bag of 7 73.2347107
  identical nucleons, go on folks! ***
   30000000 70000000 70000000 4.8488471E-04 1.0000000E+30 21067915
 NEXT SEEDS:126873E2 31 0 0 0 0 15A0C 17C 0 0
   32000000 68000000 68000000 4.8487821E-04 1.0000000E+30 22471901
 NEXT SEEDS:235A99EE 34 0 0 0 0 15A0C 17C 0 0
  *** Frmbrk: we are dealing with a bag of 7 103.968979
  identical nucleons, go on folks! ***
   34000000 66000000 66000000 4.8489894E-04 1.0000000E+30 23876715
 NEXT SEEDS:34AE2173 37 0 0 0 0 15A0C 17C 0 0
 Abort called from ICLSSF reason NO CHANNEL SELECTED Run stopped!
 STOP NO CHANNEL SELECTED
Received on Sat May 15 2010 - 11:15:40 CEST

This archive was generated by hypermail 2.2.0 : Sat May 15 2010 - 11:15:46 CEST