Skip to content

Commit

Permalink
Fix dimension ordering. Name of wout vac flag, and ensure the rp_vac …
Browse files Browse the repository at this point in the history
…variable is private.
  • Loading branch information
cianciosa committed Jul 22, 2024
1 parent e1a23b9 commit bc2d07f
Show file tree
Hide file tree
Showing 4 changed files with 14 additions and 19 deletions.
5 changes: 0 additions & 5 deletions Sources/bmw.f
Original file line number Diff line number Diff line change
Expand Up @@ -69,11 +69,6 @@ PROGRAM bmw

cl_parser => bmw_commandline_parser_class(parallel)

! Check if the required flags are set.
! IF (.not.cl_parser%is_flag_set('-mgridf')) THEN
! WRITE (*,1001) '-mgridf'
! CALL bmw_commandline_parser_print_help
! END IF
IF (.not.cl_parser%is_flag_set('-woutf')) THEN
WRITE (*,1001) '-woutf'
CALL bmw_commandline_parser_print_help
Expand Down
2 changes: 1 addition & 1 deletion Sources/bmw_commandline_parser.f
Original file line number Diff line number Diff line change
Expand Up @@ -540,7 +540,7 @@ SUBROUTINE bmw_commandline_parser_print_help
WRITE(*,*) ' '
WRITE(*,*) ' -woutf Y Specify the wout file name. '
WRITE(*,*) ' '
WRITE(*,*) ' -woutf Y Specify the wout file name. '
WRITE(*,*) ' -wvacf Y Specify the vacume wout file name. '
WRITE(*,*) ' '
WRITE(*,*) ' -siestaf Y Specify the siesta restart file name. '
WRITE(*,*) ' When this flag is used, plasma currents '
Expand Down
2 changes: 1 addition & 1 deletion Sources/unprimed_grid.f
Original file line number Diff line number Diff line change
Expand Up @@ -668,7 +668,7 @@ FUNCTION unprimed_grid_construct_c(mgrid, pgrid, pgrid_vac, &

!$OMP PARALLEL
!$OMP& DEFAULT(SHARED)
!$OMP& PRIVATE(i, ri, zi, vi, x, y, ax, ay, rp, k_p, k_m, &
!$OMP& PRIVATE(i, ri, zi, vi, x, y, ax, ay, rp, rp_vac, k_p, k_m, &
!$OMP& ar_p, ar_m, ap_p, ap_m, az_p, az_m, current)

! Multi process will do an all reduce so these arrays need to be initalized.
Expand Down
24 changes: 12 additions & 12 deletions Sources/vmec_file.f
Original file line number Diff line number Diff line change
Expand Up @@ -151,19 +151,19 @@ FUNCTION vmec_file_construct(vmec_file_name)
ALLOCATE(vmec_file_construct%presf(vmec_file_construct%ns))

ALLOCATE(vmec_file_construct%rmncf( &
& vmec_file_construct%ns, vmec_file_construct%mnmax))
& vmec_file_construct%mnmax, vmec_file_construct%ns))
ALLOCATE(vmec_file_construct%zmnsf( &
& vmec_file_construct%ns, vmec_file_construct%mnmax))
& vmec_file_construct%mnmax, vmec_file_construct%ns))

ALLOCATE(vmec_file_construct%bsupumnch( &
& vmec_file_construct%ns, vmec_file_construct%mnmax_nyq))
& vmec_file_construct%mnmax_nyq, vmec_file_construct%ns))
ALLOCATE(vmec_file_construct%bsupvmnch( &
& vmec_file_construct%ns, vmec_file_construct%mnmax_nyq))
& vmec_file_construct%mnmax_nyq, vmec_file_construct%ns))

ALLOCATE(vmec_file_construct%jksupumncf( &
& vmec_file_construct%ns, vmec_file_construct%mnmax_nyq))
& vmec_file_construct%mnmax_nyq, vmec_file_construct%ns))
ALLOCATE(vmec_file_construct%jksupvmncf( &
& vmec_file_construct%ns, vmec_file_construct%mnmax_nyq))
& vmec_file_construct%mnmax_nyq, vmec_file_construct%ns))

CALL cdf_read(vmec_ncid, 'xm', vmec_file_construct%xm)
CALL cdf_read(vmec_ncid, 'xn', vmec_file_construct%xn)
Expand All @@ -190,19 +190,19 @@ FUNCTION vmec_file_construct(vmec_file_name)

IF (vmec_file_construct%lasym) THEN
ALLOCATE(vmec_file_construct%rmnsf( &
& vmec_file_construct%ns, vmec_file_construct%mnmax))
& vmec_file_construct%mnmax, vmec_file_construct%ns))
ALLOCATE(vmec_file_construct%zmncf( &
& vmec_file_construct%ns, vmec_file_construct%mnmax))
& vmec_file_construct%mnmax, vmec_file_construct%ns))

ALLOCATE(vmec_file_construct%bsupumnsh( &
& vmec_file_construct%ns, vmec_file_construct%mnmax_nyq))
& vmec_file_construct%mnmax_nyq, vmec_file_construct%ns))
ALLOCATE(vmec_file_construct%bsupvmnsh( &
& vmec_file_construct%ns, vmec_file_construct%mnmax_nyq))
& vmec_file_construct%mnmax_nyq, vmec_file_construct%ns))

ALLOCATE(vmec_file_construct%jksupumnsf( &
& vmec_file_construct%ns, vmec_file_construct%mnmax_nyq))
& vmec_file_construct%mnmax_nyq, vmec_file_construct%ns))
ALLOCATE(vmec_file_construct%jksupvmnsf( &
& vmec_file_construct%ns, vmec_file_construct%mnmax_nyq))
& vmec_file_construct%mnmax_nyq, vmec_file_construct%ns))

CALL cdf_read(vmec_ncid, 'rmns', vmec_file_construct%rmnsf)
CALL cdf_read(vmec_ncid, 'zmnc', vmec_file_construct%zmncf)
Expand Down

0 comments on commit bc2d07f

Please sign in to comment.