Skip to content

Commit

Permalink
Make the wout file load optional.
Browse files Browse the repository at this point in the history
  • Loading branch information
cianciosa committed Feb 12, 2024
1 parent cd8a986 commit 21ccbbe
Show file tree
Hide file tree
Showing 3 changed files with 12 additions and 6 deletions.
2 changes: 1 addition & 1 deletion Sources/siesta.f90
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,7 @@ PROGRAM SIESTA
IF (lrestart) THEN
CALL context%set_restart
ELSE
CALL context%set_vmec
CALL context%set_vmec(.true.)
END IF

CALL context%converge
Expand Down
8 changes: 5 additions & 3 deletions Sources/siesta_run.f90
Original file line number Diff line number Diff line change
Expand Up @@ -379,9 +379,10 @@ SUBROUTINE siesta_run_destruct(this)
!> This method loads and sets variables based on the VMEC equilibrium. VMEC
!> controls the metric elements and coordinate system jacobian.
!>
!> @param[inout] this A @ref siesta_run_class instance.
!> @param[inout] this A @ref siesta_run_class instance.
!> @param[in] load_wout Flag to load the wout file.
!-------------------------------------------------------------------------------
SUBROUTINE siesta_run_set_vmec(this)
SUBROUTINE siesta_run_set_vmec(this, load_wout)
USE siesta_namelist, ONLY: nsin, mpolin, ntorin, nfpin, wout_file, &
l_vessel, ntor_modes
USE metrics, ONLY: init_metric_elements, LoadGrid, sqrtg
Expand All @@ -398,13 +399,14 @@ SUBROUTINE siesta_run_set_vmec(this)

! Declare Arguments
CLASS (siesta_run_class), INTENT(inout) :: this
LOGICAL, INTENT(in) :: load_wout

! local variables
INTEGER :: istat

! Start of executable code
CALL vmec_info_set_wout(wout_file, nsin, mpolin, ntorin, nfpin, &
& ntor_modes(-ntorin:ntorin))
& ntor_modes(-ntorin:ntorin), load_wout)

! CONSTRUCT R, Z, L REAL-SPACE ARRAYS ON SQRT(FLUX) - "POLAR" - MESH AND
! COMPUTE METRIC ELEMENTS AND JACOBIAN
Expand Down
8 changes: 6 additions & 2 deletions Sources/vmec_info.f90
Original file line number Diff line number Diff line change
Expand Up @@ -248,9 +248,10 @@ SUBROUTINE vmec_info_destruct_island
!> @param[in] ntor_in Number of SIESTA toroidal modes.
!> @param[in] nfp_in Number of SIESTA field periods.
!> @param[in] ntor_modes_in SIESTA Toroidal mode numbers.
!> @param[in] load_wout Flag to load the wout file.
!-------------------------------------------------------------------------------
SUBROUTINE vmec_info_set_wout(wout_file, ns_in, mpol_in, ntor_in, &
& nfp_in, ntor_modes_in)
& nfp_in, ntor_modes_in, load_wout)
USE descriptor_mod, ONLY: iam
USE v3_utilities, ONLY: assert_eq, assert
USE island_params
Expand All @@ -267,6 +268,7 @@ SUBROUTINE vmec_info_set_wout(wout_file, ns_in, mpol_in, ntor_in, &
INTEGER, INTENT(IN) :: ntor_in
INTEGER, INTENT(IN) :: nfp_in
INTEGER, DIMENSION(-ntor_in:ntor_in), INTENT(in) :: ntor_modes_in
LOGICAL :: load_wout

! Local variables
INTEGER :: istat
Expand All @@ -276,7 +278,9 @@ SUBROUTINE vmec_info_set_wout(wout_file, ns_in, mpol_in, ntor_in, &
! Start of executable code

! Load wout file.
CALL read_wout_file(wout_file, istat)
IF (load_wout) THEN
CALL read_wout_file(wout_file, istat)
END IF
CALL assert_eq(0, istat, 'Read-wout error in vmec_info_set_wout')

IF (nfp_in .lt. 1) THEN
Expand Down

0 comments on commit 21ccbbe

Please sign in to comment.