Skip to content

Commit

Permalink
THRIFT: Improve prints to command line
Browse files Browse the repository at this point in the history
  • Loading branch information
ajchcoelho committed Nov 14, 2024
1 parent f65ce10 commit e81300a
Show file tree
Hide file tree
Showing 3 changed files with 7 additions and 6 deletions.
4 changes: 2 additions & 2 deletions PENTA/Sources/penta_interface_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -861,8 +861,8 @@ SUBROUTINE penta_run_2_efield
Else
Er_test_vals(min_ind) = Er_test_vals(min_ind + 1)/2._rknd
EndIf
Write(*,'(a,i4,a,f10.3)') 'Cannot use Er=0 with log_interp, using Er(', &
min_ind, ') = ', Er_test_vals(min_ind)
! Write(*,'(a,i4,a,f10.3)') 'Cannot use Er=0 with log_interp, using Er(', &
! min_ind, ') = ', Er_test_vals(min_ind)
EndIf
! Loop over Er to get fluxes as a function of Er
Do ie = 1,num_Er_test
Expand Down
6 changes: 3 additions & 3 deletions THRIFT/Sources/thrift_dkes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -124,12 +124,12 @@ SUBROUTINE thrift_dkes(lscreen,iflag)
DO k = mystart,myend
! Setup input
arg1(1) = TRIM(proc_string)
WRITE(arg1(2),'(i3)') ik_dkes(k)
WRITE(arg1(2),'(i4)') ik_dkes(k)
WRITE(arg1(3),'(e20.10)') nuarr_dkes(k)
WRITE(arg1(4),'(e20.10)') Earr_dkes(k) !dkes_efield
arg1(5) = 'F'
IF (lscreen .and. lfirst_pass) arg1(5) = 'T'
WRITE(temp_str,'(i3.3)') k
WRITE(temp_str,'(i4.4)') k
arg1(6) = '_k' // TRIM(temp_str)
ier_phi = 0 ! We don't read the boozmn or wout file we've done that already
CALL dkes_input_prepare_old(arg1,6,dkes_input_file,ier_phi)
Expand Down Expand Up @@ -265,7 +265,7 @@ SUBROUTINE thrift_dkes(lscreen,iflag)
IF(lscreen) WRITE(*, '(I0, A, I0, A, I0, A)') k, ' in [', mystart, ',', myend, '] completed'
END DO
CALL second0(etime)
PRINT *, 'I took ', etime-stime,'s.'
WRITE(*, '(A, I0, A, F8.2, A, I0, A)') 'Processor ', myworkid, ' took ', etime-stime,'s to compute ', myend-mystart+1, ' DKES coefficients.'
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!!!!!! Parallel Work block Done
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Expand Down
3 changes: 2 additions & 1 deletion THRIFT/Sources/thrift_penta.f90
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ SUBROUTINE thrift_penta(lscreen,iflag)
!-----------------------------------------------------------------------
IF (iflag < 0) RETURN
IF (lscreen) WRITE(6,'(a)') ' -------------------- NEOCLASSICAL BOOTSTRAP USING PENTA -------------------'
IF (lscreen) WRITE(6,'(A)') " <r>/<a>"," Er root(s) (V/cm)"
IF (lscreen) Write(*,*) " <r>/<a>"," Er root(s) (V/cm)"

IF (lvmec) THEN
ierr_mpi = 0
Expand Down Expand Up @@ -174,6 +174,7 @@ SUBROUTINE thrift_penta(lscreen,iflag)
ELSE
CALL MPI_REDUCE(JBS_PENTA,JBS_PENTA,ns_dkes,MPI_DOUBLE_PRECISION,MPI_SUM,master,MPI_COMM_MYWORLD,ierr_mpi)
CALL MPI_REDUCE(etapar_PENTA,etapar_PENTA,ns_dkes,MPI_DOUBLE_PRECISION,MPI_SUM,master,MPI_COMM_MYWORLD,ierr_mpi)
CALL FLUSH(6)
DEALLOCATE(rho_k,iota,phip,chip,btheta,bzeta,bsq,vp,EparB)
DEALLOCATE(te,ne,dtedrho,dnedrho)
DEALLOCATE(ni,ti,dtidrho,dnidrho)
Expand Down

0 comments on commit e81300a

Please sign in to comment.