Skip to content

Commit

Permalink
Merge branch 'develop' into feature/STELLOPT_QI
Browse files Browse the repository at this point in the history
  • Loading branch information
lazersos committed Nov 15, 2024
2 parents 0151d90 + b93c5a5 commit 0a1eca3
Show file tree
Hide file tree
Showing 37 changed files with 2,205 additions and 147 deletions.
5 changes: 4 additions & 1 deletion DKES/DKES.dep
Original file line number Diff line number Diff line change
Expand Up @@ -73,6 +73,9 @@ residue_dkes.o : \

vcmain.o : \
../../LIBSTELL/$(LOCTYPE)/stel_kinds.o


vimatrix.o :


vnamecl2.o : \
Expand All @@ -88,7 +91,7 @@ wrout.o : \
dkes_input.o \
dkes_realspace.o \
vnamecl2.o


dkes_input_prepare.o : \
../../LIBSTELL/$(LOCTYPE)/date_and_computer.o \
Expand Down
1 change: 1 addition & 0 deletions DKES/Sources/General/dkes_realspace.f
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ MODULE dkes_realspace
1 DKES_L11p, DKES_L33p, DKES_L31p,
2 DKES_L11m, DKES_L33m, DKES_L31m,
3 DKES_scal11, DKES_scal33, DKES_scal31
INTEGER :: DKES_NK, DKES_NC, DKES_NE

CONTAINS

Expand Down
2 changes: 0 additions & 2 deletions DKES/Sources/General/printout.f
Original file line number Diff line number Diff line change
Expand Up @@ -145,7 +145,6 @@ SUBROUTINE dkes_printout(fz1p, fz1m, fz3p, fz3m, srces)
c in the main DKES routine, only the STELLOPT routine changes this
c and allocates these arrays
IF (ALLOCATED(DKES_L11p) .and. (DKES_rad_dex > 0)) THEN
! PRINT *,'got here0'
DKES_L11p(DKES_rad_dex) = L11p
DKES_L33p(DKES_rad_dex) = L33p
DKES_L31p(DKES_rad_dex) = L31p
Expand All @@ -155,7 +154,6 @@ SUBROUTINE dkes_printout(fz1p, fz1m, fz3p, fz3m, srces)
DKES_scal11(DKES_rad_dex) = scal11
DKES_scal33(DKES_rad_dex) = scal33
DKES_scal31(DKES_rad_dex) = scal13
! PRINT *,'got here1'
END IF

c output results summary
Expand Down
8 changes: 8 additions & 0 deletions LIBSTELL/LIBSTELL.dep
Original file line number Diff line number Diff line change
Expand Up @@ -52,6 +52,14 @@ beams3d_input_mod.o: \
beams3d_globals.o : \
stel_kinds.o

thrift_globals.o : \
stel_kinds.o

thrift_input_mod.o: \
stel_kinds.o \
safe_open_mod.o \
thrift_globals.o

diagno_runtime.o : \
ezspline.o \
stel_kinds.o
Expand Down
2 changes: 2 additions & 0 deletions LIBSTELL/ObjectList
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
ObjectFiles = \
thrift_input_mod.o \
thrift_globals.o \
read_nescoil_mod.o \
stellopt_targets.o \
stellopt_vars.o \
Expand Down
2 changes: 1 addition & 1 deletion LIBSTELL/Sources/Modules/fieldlines_input_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -119,7 +119,7 @@ SUBROUTINE read_fieldlines_input(filename, istat)
END IF
READ(iunit,NML=fieldlines_input,IOSTAT=istat)
IF (istat /= 0) THEN
WRITE(6,'(A)') 'ERROR reading namelist BEAMS3D_INPUT from file: ',TRIM(filename)
WRITE(6,'(A)') 'ERROR reading namelist FIELDLINES_INPUT from file: ',TRIM(filename)
backspace(iunit)
read(iunit,fmt='(A)') line
write(6,'(A)') 'Invalid line in namelist: '//TRIM(line)
Expand Down
76 changes: 76 additions & 0 deletions LIBSTELL/Sources/Modules/thrift_globals.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,76 @@
!-----------------------------------------------------------------------
! Module: thrift_globals
! Authors: S. Lazerson ([email protected])
! Date: 10/16/2024
! Description: This module contains the THRIFT global variables
! needed by the input namelist.
!-----------------------------------------------------------------------
MODULE thrift_globals
!-----------------------------------------------------------------------
! Libraries
!-----------------------------------------------------------------------
USE stel_kinds, ONLY: rprec

!-----------------------------------------------------------------------
! Module Variables
!-----------------------------------------------------------------------
IMPLICIT NONE

! Moved from thrift_vars
LOGICAL :: lverbj, leccd, lnbcd, lohmic
INTEGER :: nrho, ntimesteps, n_eq, npicard, nsj
REAL(rprec) :: tstart, tend, jtol, picard_factor, boot_factor

! Moved from thrift_vars (For ECCD in general)
INTEGER, PARAMETER :: ntime_ecrh = 200
REAL(rprec), DIMENSION(ntime_ecrh) :: PECRH_AUX_T, PECRH_AUX_F
REAL(rprec) :: ecrh_rc, ecrh_w

! Moved from thrift_vars (for TRAVIS)
INTEGER, PARAMETER :: nsys = 16
INTEGER :: nra_ecrh, nphi_ecrh
INTEGER, DIMENSION(nsys) :: wmode_ecrh
REAL(rprec), DIMENSION(nsys) :: freq_ecrh, power_ecrh
REAL(rprec), DIMENSION(nsys,3) :: antennaposition_ecrh, &
targetposition_ecrh, rbeam_ecrh, rfocus_ecrh

! Moved from thrift_vars (For DKES)
INTEGER, PARAMETER :: DKES_NS_MAX = 64
INTEGER, PARAMETER :: DKES_NSTAR_MAX = 32
INTEGER :: nruns_dkes
INTEGER, DIMENSION(:), POINTER :: DKES_rundex
INTEGER, DIMENSION(DKES_NS_MAX) :: DKES_K
REAL(rprec), DIMENSION(DKES_NSTAR_MAX) :: DKES_Erstar, DKES_Nustar

! Moved from thrift_runtime
INTEGER :: nparallel_runs, mboz, nboz
CHARACTER(256) :: bootstrap_type, eccd_type, vessel_ecrh, &
mirror_ecrh, targettype_ecrh, antennatype_ecrh, &
etapar_type



CONTAINS

! These expose the global variables through ctypes
INTEGER FUNCTION getmaxtimeecrh()
IMPLICIT NONE
getmaxtimeecrh = ntime_ecrh
END FUNCTION getmaxtimeecrh

INTEGER FUNCTION getmaxsys()
IMPLICIT NONE
getmaxsys = nsys
END FUNCTION getmaxsys

INTEGER FUNCTION getmaxns()
IMPLICIT NONE
getmaxns = DKES_NS_MAX
END FUNCTION getmaxns

INTEGER FUNCTION getmaxnstar()
IMPLICIT NONE
getmaxnstar =DKES_NSTAR_MAX
END FUNCTION getmaxnstar

END MODULE thrift_globals
Original file line number Diff line number Diff line change
Expand Up @@ -11,8 +11,7 @@ MODULE thrift_input_mod
! Libraries
!-----------------------------------------------------------------------
USE stel_kinds, ONLY: rprec
USE thrift_vars
USE thrift_runtime
USE thrift_globals
USE safe_open_mod

!-----------------------------------------------------------------------
Expand All @@ -36,6 +35,7 @@ MODULE thrift_input_mod
rfocus_ecrh, nra_ecrh, nphi_ecrh, &
freq_ecrh, power_ecrh, &
pecrh_aux_t, pecrh_aux_f, ecrh_rc, ecrh_w, &
dkes_k, dkes_Erstar, dkes_Nustar, &
etapar_type

!-----------------------------------------------------------------------
Expand Down Expand Up @@ -86,6 +86,10 @@ SUBROUTINE init_thrift_input
rfocus_ecrh = 0
nra_ecrh = 0
nphi_ecrh = 8
! DKES Vars
dkes_k = -1
dkes_Erstar = 1E10
dkes_Nustar = 1E10
RETURN
END SUBROUTINE init_thrift_input

Expand All @@ -104,21 +108,29 @@ SUBROUTINE read_thrift_input(filename, istat)
INQUIRE(FILE=TRIM(filename),EXIST=lexist)
IF (.not.lexist) stop 'Could not find input file'
CALL safe_open(iunit,istat,TRIM(filename),'old','formatted')
IF (istat /= 0) CALL handle_err(NAMELIST_READ_ERR,'thrift_input in: '//TRIM(filename),istat)
IF (istat /= 0) THEN
WRITE(6,'(A)') 'ERROR opening file: ',TRIM(filename)
CALL FLUSH(6)
STOP
END IF
READ(iunit,NML=thrift_input,IOSTAT=istat)
IF (istat /= 0) THEN
WRITE(6,'(A)') 'ERROR reading namelist THRIFT_INPUT from file: ',TRIM(filename)
backspace(iunit)
read(iunit,fmt='(A)') line
write(6,'(A)') 'Invalid line in namelist: '//TRIM(line)
CALL handle_err(NAMELIST_READ_ERR,'thrift_input in: '//TRIM(filename),istat)
CALL FLUSH(6)
STOP
END IF
CLOSE(iunit)
END IF

CALL tolower(bootstrap_type)
CALL tolower(etapar_type)
CALL tolower(eccd_type)
leccd = eccd_type .ne. ''
nsj = nrho;
nsj = nrho
nruns_dkes = COUNT(dkes_k>0)*COUNT(dkes_Erstar<1E10)*COUNT(dkes_Nustar<1E10)
RETURN
END SUBROUTINE read_thrift_input

Expand Down Expand Up @@ -154,6 +166,7 @@ SUBROUTINE write_thrift_namelist(iunit_out, istat)
WRITE(iunit_out,outint) 'MBOZ',nboz
WRITE(iunit_out,'(A)') '!---------- ECCD PARAMETERS ------------'
WRITE(iunit_out,outstr) 'ECCD_TYPE',eccd_type
WRITE(iunit_out,'(A)') '!---------- DKES PARAMETERS ------------'
WRITE(iunit_out,'(A)') '/'
RETURN
END SUBROUTINE write_thrift_namelist
Expand Down
1 change: 1 addition & 0 deletions PENTA/ObjectList
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
ObjectFiles = \
penta_interface_mod.o \
bspline.o \
coeff_var_pass.o \
io_unit_spec.o \
Expand Down
15 changes: 15 additions & 0 deletions PENTA/PENTA.dep
Original file line number Diff line number Diff line change
@@ -1,4 +1,7 @@
# Microsoft Developer Studio Generated Dependency File, included by DKES.mak
penta_main.o : \
penta_modules.o


bspline.o :

Expand All @@ -17,6 +20,18 @@ penta.o : \
penta_math_routines_mod.o \
penta_subroutines.o

penta_interface_mod.o : \
penta_kind_mod.o \
io_unit_spec.o \
read_input_file_mod.o \
vmec_var_pass.o \
pprof_pass.o \
coeff_var_pass.o \
phys_const.o \
penta_functions_mod.o \
penta_math_routines_mod.o \
penta_subroutines.o

penta_functions_mod.o : \
penta_kind_mod.o \
phys_const.o \
Expand Down
2 changes: 1 addition & 1 deletion PENTA/Sources/io_unit_spec.f90
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ Module io_unit_spec

Implicit none

Integer, parameter :: &
Integer :: &
iu_nl=21, & ! Ion parameter namelist file (input)
iu_vmec=22, & ! VMEC data file (input)
iu_pprof=23, & ! Plasma profile file (input)
Expand Down
Loading

0 comments on commit 0a1eca3

Please sign in to comment.