gray/src/gray_params.f90

209 lines
6.7 KiB
Fortran
Raw Normal View History

2015-11-18 17:34:33 +01:00
module gray_params
use const_and_precisions, only : wp_
implicit none
integer, parameter :: lenfnm=256
type antctrl_type
real(wp_) :: alpha, beta, power
real(wp_) :: psi, chi
integer :: iox
integer :: ibeam
character(len=lenfnm) :: filenm
end type antctrl_type
type eqparam_type
real(wp_) :: ssplps, ssplf, factb
integer :: sgnb, sgni, ixp
integer :: iequil, icocos, ipsinorm, idesc, ifreefmt
character(len=lenfnm) :: filenm
end type eqparam_type
type prfparam_type
real(wp_) :: psnbnd, sspld, factne, factte
integer :: iscal, irho !, icrho, icte, icne, iczf
integer :: iprof
character(len=lenfnm) :: filenm
end type prfparam_type
type rtrparam_type
real(wp_) :: rwmax, dst
integer :: nrayr, nrayth, nstep
integer :: igrad, idst, ipass, ipol
end type rtrparam_type
type hcdparam_type
integer :: iwarm, ilarm, imx, ieccd
end type hcdparam_type
type outparam_type
integer :: ipec, nrho, istpr, istpl
end type outparam_type
integer, save :: iequil,iprof,ipol
integer, save :: iwarm,ilarm,imx,ieccd
integer, save :: igrad,idst,ipass
integer, save :: istpr0,istpl0
integer, save :: ipec,nnd
contains
subroutine read_inputs(filenm,antctrl,eqparam,rwall,prfparam,outparam,unit)
use const_and_precisions, only : wp_
use utils, only : get_free_unit
implicit none
! arguments
character(len=*), intent(in) :: filenm
type(antctrl_type), intent(out) :: antctrl
type(eqparam_type), intent(out) :: eqparam
real(wp_), intent(out) :: rwall
type(prfparam_type), intent(out) :: prfparam
type(outparam_type), intent(out) :: outparam
integer, intent(in), optional :: unit
! local variables
integer :: u
if (present(unit)) then
u=unit
else
u = get_free_unit()
end if
open(u,file=filenm,status= 'old',action='read')
! alpha0, beta0 (cartesian) launching angles
read(u,*) antctrl%alpha, antctrl%beta
! p0mw injected power (MW)
read(u,*) antctrl%power
! abs(iox)=1/2 OM/XM
! psipol0,chipol0 polarization angles at the antenna (if iox<0)
read(u,*) antctrl%iox, antctrl%psi, antctrl%chi
! ibeam=0 :read data for beam as above
! ibeam=1 :read data from file simple astigmatic beam
! ibeam=2 :read data from file general astigmatic beam
read(u,*) antctrl%ibeam
read(u,*) antctrl%filenm
! iequil=0 :vacuum
! iequil=1 :analytical equilibrium
! iequil=2 :read eqdsk
read(u,*) eqparam%iequil
read(u,*) eqparam%filenm
! icocos :index for equilibrium from COCOS - O. Sauter Feb 2012
! ipsinorm :0 standard EQDSK format, 1 format Portone summer 2004
read(u,*) eqparam%icocos, eqparam%ipsinorm, eqparam%idesc, eqparam%ifreefmt
! ixp=0,-1,+1 : no X point , bottom/up X point
! ssplps : spline parameter for psi interpolation
read(u,*) eqparam%ixp, eqparam%ssplps !, eqparam%ssplf
eqparam%ssplf=0.01_wp_
! signum of toroidal B and I
! factb factor for magnetic field (only for numerical equil)
! scaling adopted: beta=const, qpsi=const, nustar=const
read(u,*) eqparam%sgnb, eqparam%sgni, eqparam%factb
read(u,*) rwall
! iprof=0 :analytical density and temp. profiles
! iprof>0 :numerical density and temp. profiles
read(u,*) prfparam%iprof, prfparam%irho ! irho=0,1,2 -> num profiles vs rhot,rhop,psin
read(u,*) prfparam%filenm
! psbnd value of psi ( > 1 ) of density boundary
read(u,*) prfparam%psnbnd !, prfparam%sspld
prfparam%sspld=0.001_wp_
! iscal ne Te scaling 0: nustar=const, 1: n_greenw=const; 2 no rescaling
! factT factn factor for Te&ne scaling
read(u,*) prfparam%factte, prfparam%factne, prfparam%iscal
! ipec=0/1 :pec profiles grid in psi/rhop
! nrho :number of grid steps for pec profiles +1
read(u,*) outparam%ipec, outparam%nrho
! istpr0 projection step = dsdt*istprj
! istpl0 plot step = dsdt*istpl
read(u,*) outparam%istpr, outparam%istpl
close(u)
end subroutine read_inputs
subroutine read_params(filenm,rtrparam,hcdparam,unit)
use utils, only : get_free_unit
implicit none
! arguments
character(len=*), intent(in) :: filenm
type(rtrparam_type), intent(out) :: rtrparam
type(hcdparam_type), intent(out) :: hcdparam
integer, intent(in), optional :: unit
! local variables
integer :: u
if (present(unit)) then
u=unit
else
u = get_free_unit()
end if
open(u,file=filenm,status= 'old',action='read')
! nrayr number of rays in radial direction
! nrayth number of rays in angular direction
! rwmax normalized maximum radius of beam power
! rwmax=1 -> last ray at radius = waist
read(u,*) rtrparam%nrayr, rtrparam%nrayth, rtrparam%rwmax
! igrad=0 optical ray-tracing, initial conditions as for beam
! igrad=1 quasi-optical ray-tracing
! igrad=-1 ray-tracing, init. condit.
! from center of mirror and with angular spread
! ipass=1/2 1 or 2 passes into plasma
! ipol=0 compute mode polarization at antenna, ipol=1 use polariz angles
read(u,*) rtrparam%igrad, rtrparam%ipass, rtrparam%ipol
! dst integration step
! nstep maximum number of integration steps
! idst=0/1/2 0 integration in s, 1 integr. in ct, 2 integr. in Sr
read(u,*) rtrparam%dst, rtrparam%nstep, rtrparam%idst
! iwarm=0 :no absorption and cd
! iwarm=1 :weakly relativistic absorption
! iwarm=2 :relativistic absorption, n<1 asymptotic expansion
! iwarm=3 :relativistic absorption, numerical integration
! ilarm :order of larmor expansion
! imx :max n of iterations in dispersion, imx<0 uses 1st
! iteration in case of failure after |imx| iterations
read(u,*) hcdparam%iwarm,hcdparam%ilarm,hcdparam%imx
! ieccd 0/1 NO/YES ECCD calculation ieccd>0 different CD models
read(u,*) hcdparam%ieccd
close(u)
end subroutine read_params
subroutine set_codepar(eqparam,prfparam,outparam,rtrparam,hcdparam)
implicit none
type(eqparam_type), intent(in) :: eqparam
type(prfparam_type), intent(in) :: prfparam
type(outparam_type), intent(in) :: outparam
type(rtrparam_type), intent(in) :: rtrparam
type(hcdparam_type), intent(in) :: hcdparam
iequil=eqparam%iequil
iprof=prfparam%iprof
ipec=outparam%ipec
nnd=outparam%nrho
istpr0=outparam%istpr
istpl0=outparam%istpl
ipol=rtrparam%ipol
igrad=rtrparam%igrad
idst=rtrparam%idst
ipass=rtrparam%ipass
if (rtrparam%nrayr<5) then
igrad=0
print*,' nrayr < 5 ! => OPTICAL CASE ONLY'
print*,' '
end if
iwarm=hcdparam%iwarm
ilarm=hcdparam%ilarm
imx=hcdparam%imx
ieccd=hcdparam%ieccd
end subroutine set_codepar
end module gray_params