Skip to content

Commit

Permalink
Merge pull request #238 from PrincetonUniversity/bugfix/STELLOPT_iflag
Browse files Browse the repository at this point in the history
STELLOPT: Issue where iflag/=0 was not being caught by subcodes.
  • Loading branch information
lazersos authored May 22, 2024
2 parents 48dcb0d + b4928ba commit b3f032c
Showing 1 changed file with 33 additions and 9 deletions.
42 changes: 33 additions & 9 deletions STELLOPTV2/Sources/General/stellopt_fcn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -403,7 +403,7 @@ SUBROUTINE stellopt_fcn(m, n, x, fvec, iflag, ncnt)
dex = MINLOC(am_aux_s(2:),DIM=1)
IF (dex > 2) THEN
IF (ANY(am_aux_f(1:dex) < 0)) iflag = -55
IF (ALL(am_aux_f(1:dex) == 0)) iflag = -55
!IF (ALL(am_aux_f(1:dex) == 0)) iflag = -55
END IF
IF (pres_scale < 0) iflag = -55
! Now call any functions necessary to read or load the
Expand All @@ -418,24 +418,45 @@ SUBROUTINE stellopt_fcn(m, n, x, fvec, iflag, ncnt)
proc_string_old = proc_string ! So we can find the DIAGNO files
IF (ANY(sigma_balloon < bigno)) CALL stellopt_balloon(lscreen,iflag)
ctemp_str = 'booz_xform'
IF (ANY(lbooz) .and. (iflag>=0)) CALL stellopt_paraexe(ctemp_str,proc_string,lscreen); iflag = ier_paraexe
IF (ANY(lbooz) .and. (iflag>=0)) THEN
CALL stellopt_paraexe(ctemp_str,proc_string,lscreen)
iflag = ier_paraexe
END IF
ctemp_str = 'bootsj'
IF (ANY(sigma_bootstrap < bigno) .and. (iflag>=0)) CALL stellopt_paraexe(ctemp_str,proc_string,lscreen); iflag = ier_paraexe
IF (ANY(sigma_bootstrap < bigno) .and. (iflag>=0)) THEN
CALL stellopt_paraexe(ctemp_str,proc_string,lscreen)
iflag = ier_paraexe
END IF
ctemp_str = 'diagno'
IF (lneed_magdiag .and. (iflag>=0)) CALL stellopt_paraexe(ctemp_str,proc_string,lscreen); iflag = ier_paraexe
IF (lneed_magdiag .and. (iflag>=0)) THEN
CALL stellopt_paraexe(ctemp_str,proc_string,lscreen)
iflag = ier_paraexe
END IF
ctemp_str = 'neo'
IF (ANY(sigma_neo < bigno) .and. (iflag>=0)) CALL stellopt_paraexe(ctemp_str,proc_string,lscreen); iflag = ier_paraexe
IF (ANY(sigma_neo < bigno) .and. (iflag>=0)) THEN
CALL stellopt_paraexe(ctemp_str,proc_string,lscreen)
iflag = ier_paraexe
END IF
!DEC$ IF DEFINED (TERPSICHORE)
ctemp_str = 'terpsichore'
IF (ANY(sigma_kink < bigno) .and. (iflag>=0)) CALL stellopt_paraexe(ctemp_str,proc_string,lscreen); iflag = ier_paraexe
IF (ANY(sigma_kink < bigno) .and. (iflag>=0)) THEN
CALL stellopt_paraexe(ctemp_str,proc_string,lscreen)
iflag = ier_paraexe
END IF
!DEC$ ENDIF
!DEC$ IF DEFINED (TRAVIS)
ctemp_str = 'travis'
IF (ANY(sigma_ece < bigno) .and. (iflag>=0)) CALL stellopt_paraexe(ctemp_str,proc_string,lscreen); iflag = ier_paraexe
IF (ANY(sigma_ece < bigno) .and. (iflag>=0)) THEN
CALL stellopt_paraexe(ctemp_str,proc_string,lscreen)
iflag = ier_paraexe
END IF
!DEC$ ENDIF
!DEC$ IF DEFINED (DKES_OPT)
ctemp_str = 'dkes'
IF ((ANY(sigma_dkes < bigno).or.ANY(sigma_dkes_erdiff < bigno).or.ANY(sigma_dkes_alpha < bigno)) .and. (iflag>=0)) CALL stellopt_paraexe(ctemp_str,proc_string,lscreen); iflag = ier_paraexe
IF ((ANY(sigma_dkes < bigno).or.ANY(sigma_dkes_erdiff < bigno).or.ANY(sigma_dkes_alpha < bigno)) .and. (iflag>=0)) THEN
CALL stellopt_paraexe(ctemp_str,proc_string,lscreen)
iflag = ier_paraexe
END IF
!DEC$ ENDIF

! NOTE ALL parallel secondary codes go here
Expand All @@ -447,7 +468,10 @@ SUBROUTINE stellopt_fcn(m, n, x, fvec, iflag, ncnt)
!DEC$ ENDIF
!DEC$ IF DEFINED (COILOPTPP)
ctemp_str = 'coilopt++'
IF (sigma_coil_bnorm < bigno .and. (iflag>=0)) CALL stellopt_paraexe(ctemp_str,proc_string,lscreen); iflag = ier_paraexe
IF (sigma_coil_bnorm < bigno .and. (iflag>=0)) THEN
CALL stellopt_paraexe(ctemp_str,proc_string,lscreen)
iflag = ier_paraexe
END IF
!DEC$ ENDIF
!DEC$ IF DEFINED (REGCOIL)
! JCS: skipping parallelization for now
Expand Down

0 comments on commit b3f032c

Please sign in to comment.