ATIMA-8
拙作のATIMAラッパのソース
IMPLICIT NONE
INCLUDE 'atima.1.2/src/atima/system.inc'

c Variables
c------Parameters which should be given-------
!of Projectile
INTEGER Zpa
REAL*8 Mpa,en

!of Material
INTEGER iGas, nNucl
INTEGER Za(maxnuc), stnr(maxnuc)
REAL*8 Ma(maxnuc), IValue(maxnuc)
REAL*8 density, fntpa, GIValue
REAL*8 thick
c---------------------------------------------

REAL*8 eo,range,dedxi,dedxo,remra,rstr,estr,astr,tof

INTEGER FG(8)
REAL*8 t1(1000), t2(1000), t3(1000), t4(1000)
REAL*8 bc1(1000), bc2(1000), bc3(1000), bc4(1000)

c Program
call GetGivenParameters( Zpa, Mpa, en,
& iGas, nNucl, Za, stnr, Ma, IValue,
& density, fntpa, GIValue, thick)

c iGas = 1
c nNucl = 1
c thick = 10.0
c Za(1) = 2
c Ma(1) = 4.0026
c IValue(1) = 41.8
c stnr(1) = 1.0
rho = density
c fntpa = 1
GIValue = 0.0d0
c
c Zpa = 82
c Mpa = 206.976
en = 82.0

eo = -1.0

call ATIMA( nNucl, iGas, fntpa, GIValue,
& rho, Zpa, Mpa, Za, Ma, IValue, stnr, FG)
call SplinesLesen( FG(1), FG(2), t1, bc1, FG(3), FG(4), t2, bc2,
& FG(5), FG(6), t3, bc3, FG(7), FG(8), t4, bc4 )
call SpGroessenNeu( FG(1), FG(2), t1, bc1,
& FG(3), FG(4), t2, bc2,
& FG(5), FG(6), t3, bc3, FG(7), FG(8), t4, bc4,
& en, thick, eo,
& range,dedxi,dedxo,remra,rstr,estr,
& astr,tof )

write(*,*) "Rest K [MeV/u]->", eo
write(*,*) "Range [mg/cm^2]->", range
write(*,*) "Rest Range ->", remra
write(*,*) "dE/dx in[MeV/sden]->", dedxi*Mpa
write(*,*) "Range Straggling->", rstr
write(*,*) "K? Straggling->", estr
write(*,*) "Angular Straggling->", astr
write(*,*) "Time of Flight ->", tof

END



subroutine GetGivenParameters( Zpa, Mpa, en,
& iGas, nNucl, Za, stnr, Ma, IValue,
& density, fntpa, GIValue, thick)
implicit none
INCLUDE 'atima.1.2/src/atima/system.inc'
c------Parameters which should be given-------
!of Projectile
INTEGER Zpa
REAL*8 Mpa,en

!of Material
INTEGER iGas, nNucl
INTEGER Za(maxnuc), stnr(maxnuc)
REAL*8 Ma(maxnuc), IValue(maxnuc)
REAL*8 fntpa, GIValue, density, thick
c---------------------------------------------
INTEGER unit, i
REAL*8 temp

c FORMAT is same to calcint-out + thickness

unit = 16
open(unit,file='tele.dat')
c Read Projectile
read(unit,*) Zpa, Mpa
c Read Mateial
read(unit,*) nNucl
c Read Compoments
do i = 1, nNucl
read(unit,*) Za(i), temp, IValue(i), Ma(i)
stnr(i) = temp
enddo
970 FORMAT (I4,D15.6,D15.6,D15.6)
c Read General
read(unit,*) density, iGas, fntpa
read(unit,*) thick

close(unit)
end