added file headers with input parameters

This commit is contained in:
Lorenzo Figini 2016-04-27 14:37:57 +00:00
parent a5199b1b24
commit d7b09b92a2
2 changed files with 137 additions and 13 deletions

View File

@ -2,6 +2,7 @@ module gray_params
use const_and_precisions, only : wp_
implicit none
integer, parameter :: lenfnm=256
integer, parameter :: headw=132,headl=21
type antctrl_type
real(wp_) :: alpha, beta, power
@ -48,6 +49,97 @@ module gray_params
contains
subroutine print_params(rtrparam,hcdparam,antctrl,eqparam,rwall, &
prfparam,outparam,strout)
implicit none
! arguments
type(rtrparam_type), intent(in) :: rtrparam
type(hcdparam_type), intent(in) :: hcdparam
type(antctrl_type), intent(in) :: antctrl
type(eqparam_type), intent(in) :: eqparam
real(wp_), intent(in) :: rwall
type(prfparam_type), intent(in) :: prfparam
type(outparam_type), intent(in) :: outparam
character(len=*), dimension(:), intent(out) :: strout ! min len=110, dimension(21)
! local variables
character(len=8) :: rdat
character(len=10) :: rtim
#ifndef REVISION
character(len=*), parameter :: REVISION="unknown"
#endif
! date and time
call date_and_time(rdat,rtim)
write(strout(1),'("# Run date/time: ",a4,2("/",a2),1x,2(a2,":"),a6)') &
rdat(1:4),rdat(5:6),rdat(7:8),rtim(1:2),rtim(3:4),rtim(5:10)
! SVN revision
write(strout(2),'("# GRAY SVN revision: ",a)') REVISION
! equilibrium input data
if (eqparam%iequil > 0) then
write(strout(3),'("# EQL input: ",a)') trim(eqparam%filenm)
!!!!!!! missing values
write(strout(7),'("# EQL B0 R0 aminor Rax zax:",5(1x,e12.5))') &
0._wp_, 0._wp_, 0._wp_, 0._wp_, 0._wp_
else
write(strout(3),'("# EQL input: N/A (vacuum)")')
write(strout(7),'("# EQL B0 R0 aminor Rax zax: N/A (vacuum)")')
end if
write(strout(4),'("# EQL iequil sgnb sgni factb:",3(1x,i4),1x,e12.5)') &
eqparam%iequil, eqparam%sgnb, eqparam%sgni, eqparam%factb
if (eqparam%iequil > 1) then
write(strout(5),'("# EQL icocos ipsinorm idesc ifreefmt:",4(1x,i4))') &
eqparam%icocos, eqparam%ipsinorm, eqparam%idesc, eqparam%ifreefmt
write(strout(6),'("# EQL ssplps ssplf ixp:",2(1x,e12.5),1x,i4)') &
eqparam%ssplps, eqparam%ssplf, eqparam%ixp
else
write(strout(5),'("# EQL icocos ipsinorm idesc ifreefmt: N/A (analytical)")')
write(strout(6),'("# EQL ssplps ssplf ixp: N/A (analytical)")')
end if
! profiles input data
if (eqparam%iequil > 0) then
write(strout(8),'("# PRF input: ",a)') trim(prfparam%filenm)
write(strout(9),'("# PRF iprof iscal factne factte:",2(1x,i4),2(1x,e12.5))') &
prfparam%iprof,prfparam%iscal,prfparam%factne,prfparam%factte
if (prfparam%iprof > 0) then
write(strout(10),'("# PRF irho psnbnd sspld:",1x,i4,2(1x,e12.5))') &
prfparam%irho,prfparam%psnbnd,prfparam%sspld
else
write(strout(10),'("# PRF irho psnbnd sspld: N/A (analytical)")')
end if
!!!!!!! missing values
write(strout(11),'("# PRF Te0 ne0 Zeff0:",3(1x,e12.5))') &
0._wp_, 0._wp_, 0._wp_
else
write(strout(8),'("# PRF input: N/A (vacuum)")')
write(strout(9),'("# PRF iprof iscal factne factte: N/A (vacuum)")')
write(strout(10),'("# PRF irho psnbnd sspld: N/A (vacuum)")')
write(strout(11),'("# PRF Te0 ne0 Zeff0: N/A (vacuum)")')
end if
! launch parameters
write(strout(12),'("# ANT input: ",a)') trim(antctrl%filenm)
write(strout(13),'("# ANT ibeam iox psi chi:",2(1x,i4),2(1x,e12.5))') &
antctrl%ibeam, antctrl%iox, antctrl%psi, antctrl%chi
write(strout(14),'("# ANT alpha beta power:",3(1x,e12.5))') &
antctrl%alpha, antctrl%beta, antctrl%power
!!!!!!! missing values
write(strout(15),'("# ANT x0 y0 z0:",3(1x,e12.5))') &
0._wp_, 0._wp_, 0._wp_
!!!!!!! missing values
write(strout(16),'("# ANT wx wy Rcix Rciy psiw psir:",6(1x,e12.5))') &
0._wp_, 0._wp_, 0._wp_, 0._wp_, 0._wp_, 0._wp_
! wall parameters
write(strout(17),'("# RFL rwall:",1x,e12.5)') rwall
! code parameters
write(strout(18),'("# COD igrad idst ipass ipol:",4(1x,i4))') &
rtrparam%igrad, rtrparam%idst, rtrparam%ipass, rtrparam%ipol
write(strout(19),'("# COD nrayr nrayth nstep rwmax dst:",3(1x,i4),2(1x,e12.5))') &
rtrparam%nrayr, rtrparam%nrayth, rtrparam%nstep, rtrparam%rwmax, rtrparam%dst
write(strout(20),'("# COD iwarm ilarm imx ieccd:",4(1x,i4))') &
hcdparam%iwarm, hcdparam%ilarm, hcdparam%imx, hcdparam%ieccd
write(strout(21),'("# COD ipec nrho istpr istpl:",4(1x,i4))') &
outparam%ipec, outparam%nrho, outparam%istpr, outparam%istpl
end subroutine print_params
subroutine read_params(filenm,rtrparam,hcdparam,antctrl,eqparam,rwall, &
prfparam,outparam,unit)
use utils, only : get_free_unit

View File

@ -12,8 +12,8 @@ contains
use coreprofiles, only : set_prfan, set_prfspl, temp, fzeff
use dispersion, only : expinit
use gray_params, only : eqparam_type, prfparam_type, outparam_type, &
rtrparam_type, hcdparam_type, set_codepar, iequil, iprof, ieccd, &
iwarm, ipec, istpr0, igrad
rtrparam_type, hcdparam_type, antctrl_type, set_codepar, print_params, &
iequil, iprof, ieccd, iwarm, ipec, istpr0, igrad, headw, headl
use beams, only : read_beam0, read_beam1, launchangles2n, xgygcoeff
use beamdata, only : pweight, rayi2jk
use equilibrium, only : set_equian, set_eqspl, setqphi_num, set_rhospl, &
@ -52,7 +52,7 @@ contains
real(wp_), parameter :: taucr = 12._wp_
real(wp_), dimension(:), allocatable :: rhotn
real(wp_) :: sox,ak0,bres,xgcn,xg,yg,zzm,alpha,didp,anpl,anpr,anprim,anprre
real(wp_) :: chipol,psipol,btot,psinv,dens,tekev,dersdst,derdnm,st,st0
real(wp_) :: tau,pow,dids,ddr,ddi,taumn,taumx
@ -73,6 +73,11 @@ contains
real(wp_), dimension(:), allocatable :: jphi,pins,currins
! parameters log in file headers
character(len=headw), dimension(headl) :: strheader
type(antctrl_type) :: antp
real(wp_) :: rwall
! ======= set environment BEGIN ======
call set_codepar(eqp,prfp,outp,rtrp,hcdp)
@ -104,7 +109,18 @@ contains
! ======= set environment END ======
! ======= pre-proc prints BEGIN ======
call print_headers
antp%alpha=alpha0
antp%beta=beta0
antp%power=p0
antp%psi=psipol0
antp%chi=chipol0
antp%iox=iox0
!!!!! missing values
antp%ibeam=0
antp%filenm=''
rwall=0._wp_
call print_params(rtrp,hcdp,antp,eqp,rwall,prfp,outp,strheader)
call print_headers(strheader)
! print psi surface for q=1.5 and q=2 on file and psi,rhot,rhop on stdout
call print_surfq((/1.5_wp_,2.0_wp_/))
! print
@ -1645,18 +1661,34 @@ bb: do
subroutine print_headers
subroutine print_headers(strheader)
use units, only : uprj0,uwbm,udisp,ucenr,uoutr,upec,usumm
implicit none
write(uprj0,*) ' #sst j k xt yt zt rt'
write(uprj0+1,*) ' #sst j k xt yt zt rt'
write(uwbm,*) ' #sst w1 w2'
write(udisp,*) ' #sst Dr_Nr Di_Nr'
write(ucenr,*) ' #sst R z phi psin rhot ne Te Btot Bx By Bx Nperp Npl '// &
! arguments
character(len=*), dimension(:), intent(in) :: strheader
! local variables
integer :: i,l
l=size(strheader)
do i=1,l
write(uprj0,'(1x,a)') strheader(i)
write(uprj0+1,'(1x,a)') strheader(i)
write(uwbm,'(1x,a)') strheader(i)
write(udisp,'(1x,a)') strheader(i)
write(ucenr,'(1x,a)') strheader(i)
write(uoutr,'(1x,a)') strheader(i)
write(upec,'(1x,a)') strheader(i)
write(usumm,'(1x,a)') strheader(i)
end do
write(uprj0,'(1x,a)') '#sst j k xt yt zt rt'
write(uprj0+1,'(1x,a)') '#sst j k xt yt zt rt'
write(uwbm,'(1x,a)') '#sst w1 w2'
write(udisp,'(1x,a)') '#sst Dr_Nr Di_Nr'
write(ucenr,'(1x,a)') '#sst R z phi psin rhot ne Te Btot Bx By Bx Nperp Npl '// &
'Nx Ny Nz ki alpha tau Pt dIds nhmax iohkw index_rt ddr'
write(uoutr,*) ' #i k sst x y R z psin tau Npl alpha index_rt'
write(upec,*) ' #rhop rhot Jphi Jcdb dPdV Icdins Pins index_rt'
write(usumm,*) ' #Icd Pa Jphip dPdVp rhotj rhotjava rhotp rhotpav ' // &
write(uoutr,'(1x,a)') '#i k sst x y R z psin tau Npl alpha index_rt'
write(upec,'(1x,a)') '#rhop rhot Jphi Jcdb dPdV Icdins Pins index_rt'
write(usumm,'(1x,a)') '#Icd Pa Jphip dPdVp rhotj rhotjava rhotp rhotpav ' // &
'drhotjava drhotpav ratjamx ratjbmx stmx psipol chipol index_rt ' // &
'Jphimx dPdVmx drhotj drhotp'
end subroutine print_headers