Skip to content

Commit

Permalink
PENTA: Subroutine interface checked.
Browse files Browse the repository at this point in the history
  • Loading branch information
lazersos committed Oct 17, 2024
1 parent 9b8e4c5 commit cd12712
Showing 1 changed file with 8 additions and 8 deletions.
16 changes: 8 additions & 8 deletions PENTA/Sources/penta_interface_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -133,7 +133,7 @@ SUBROUTINE read_penta_run_params_namelist(filename,istat)
END IF
READ(iunit,NML=run_params,IOSTAT=istat)
IF (istat /= 0) THEN
WRITE(6,'(A)') 'ERROR reading PENTA ion_params namelist from file: ',TRIM(filename)
WRITE(6,'(A)') 'ERROR reading PENTA run_params namelist from file: ',TRIM(filename)
backspace(iunit)
read(iunit,fmt='(A)') line
write(6,'(A)') 'Invalid line in namelist: '//TRIM(line)
Expand Down Expand Up @@ -280,7 +280,6 @@ SUBROUTINE penta_read_input_files
USE coeff_var_pass, ONLY: D11_mat, cmul, num_c
USE phys_const, ONLY: p_mass, elem_charge, e_mass
USE read_input_file_mod
USE PENTA_subroutines, ONLY : define_friction_coeffs
IMPLICIT NONE
CALL read_vmec_file_2(js,run_ident)
CALL read_pprof_file(pprof_char,num_ion_species,roa_surf,arad,kord_pprof)
Expand All @@ -298,7 +297,7 @@ SUBROUTINE penta_read_input_files
U2=1.5d0*D11_mat(num_c,1)/cmul(num_c);
ENDIF
! Change Er test range to V/cm if necessary
IF ( input_is_Er) THEN
IF ( .not. input_is_Er) THEN
Er_min = Er_min * Te / arad
Er_max = Er_max * Te / arad
ENDIF
Expand All @@ -322,9 +321,6 @@ SUBROUTINE penta_read_input_files
vths=(/vth_e,vth_i/)
dTdrs=(/dTedr,dTidr/)
dndrs=(/dnedr,dnidr/)
! Define matrix of friction coefficients (lmat)
Call define_friction_coeffs(masses,charges,vths,Temps,dens,loglambda, &
num_species,Smax,lmat)
RETURN
END SUBROUTINE penta_read_input_files

Expand Down Expand Up @@ -412,7 +408,7 @@ SUBROUTINE penta_open_output
! Set write status
IF (i_append == 0) THEN
fstatus = "unknown"
fpos = "asis"
fpos = "SEQUENTIAL"
ELSEIF (i_append == 1) THEN
fstatus = "old"
fpos = "append"
Expand Down Expand Up @@ -490,8 +486,11 @@ END SUBROUTINE penta_open_output
SUBROUTINE penta_fit_rad_trans
USE coeff_var_pass
USE vmec_var_pass
USE PENTA_subroutines, ONLY : fit_coeffs
USE PENTA_subroutines, ONLY : fit_coeffs, define_friction_coeffs
IMPLICIT NONE
! Define matrix of friction coefficients (lmat)
Call define_friction_coeffs(masses,charges,vths,Temps,dens,loglambda, &
num_species,Smax,lmat)
! Fit radial transport coefficients specific to different methods
SELECT CASE (Method)
CASE ('T', 'MBT')
Expand Down Expand Up @@ -537,6 +536,7 @@ END SUBROUTINE penta_fit_rad_trans
SUBROUTINE penta_run_1_init
IMPLICIT NONE
INTEGER :: istat
CALL init_penta_input
istat = 0
CALL read_penta_ion_params_namelist('ion_params',istat)
istat = 0
Expand Down

0 comments on commit cd12712

Please sign in to comment.