Skip to content

Commit

Permalink
Merge pull request LLNL#58 from LLNL/develop
Browse files Browse the repository at this point in the history
Fixes merge issues that removed HDF5 gridue capability
  • Loading branch information
holm10 authored Oct 28, 2023
2 parents b7794aa + 1d2844f commit a4ea519
Show file tree
Hide file tree
Showing 13 changed files with 309 additions and 88 deletions.
4 changes: 4 additions & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -5,9 +5,13 @@ build/
.idea/
.DS_Store
*~
*.swp
a.out
PyUEDGE_tutorial/*
*.swo
pyscripts/__src__.py
dist/uedge-8.0.0-py3.7-macosx-10.9-x86_64.egg
uedge.egg-info
*.egg
*.c
*.f
10 changes: 8 additions & 2 deletions api/fimp.m
Original file line number Diff line number Diff line change
Expand Up @@ -266,6 +266,8 @@ subroutine readmc(nzdf,mcfilename)
character*256 mcfilename(*)
character*256 fname
Use(Multicharge)
Use(Math_problem_size) # neqmx
Use(Lsode) # iprint
Use(Impdata) #apidir
c ... Function:
Expand Down Expand Up @@ -308,11 +310,15 @@ call xerrab("")
* un*formatted read for header data
read (nget,'(2a8,i12,4x,a32)') idcod, idtyp, n, id1
if (n .lt. 0 .and. iprt_imp_file == 1) then
write(*,*) '***Impurity file using new 2012 format is ',mcfilename(i)
if (iprint .ne. 0) then
write(*,*) '***Impurity file using new 2012 format is ',mcfilename(i)
endif
mcfformat(i) = 1
iprt_imp_file = 0
elseif (iprt_imp_file == 1) then
write(*,*) '***Impurity file using pre-2012 format is ',mcfilename(i)
if (iprint .ne. 0) then
write(*,*) '***Impurity file using pre-2012 format is ',mcfilename(i)
endif
mcfformat(i) = 0
iprt_imp_file = 0
endif
Expand Down
8 changes: 6 additions & 2 deletions api/sputt.m
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,8 @@ SUBROUTINE SYLD96(MATT,MATP,CION,CIZB,CRMB)
cdtr include 'cyield'

Use(Cyield) # ceth,cetf,cq,ntars,cidata
Use(Math_problem_size) # neqmx
Use(Lsode) # iprint

real ETH(7,12), ETF(7,12), Q(7,12), EBD(12)
LOGICAL IDATA(7,12)
Expand Down Expand Up @@ -199,9 +201,11 @@ ctdr IF (CEBD.EQ.0.0 .AND. MATT.LE.12) CEBD = EBD(MATT)
IF (CIZB.EQ.6) MATP = 5
IF (CIZB.EQ.8) MATP = 7
cdtr IF (CNEUTD.EQ.1) MATP = CBOMBF
WRITE (*,*) 'TARGET MATERIAL IS ' , TARMAT(MATT)
WRITE (*,*) 'BOMBARDING IONS ARE ' , PLAMAT(MATP)
if (iprint .ne. 0) then
WRITE (*,*) 'TARGET MATERIAL IS ' , TARMAT(MATT)
WRITE (*,*) 'BOMBARDING IONS ARE ' , PLAMAT(MATP)
cdtr IF (CNEUTD.EQ.1) CALL PRI (' WITH ZIMP', CBOMBZ)
endif
RETURN
END
C
Expand Down
23 changes: 13 additions & 10 deletions bbb/geometry.m
Original file line number Diff line number Diff line change
Expand Up @@ -448,6 +448,7 @@ logical function tstguardc (ix, iy)

implicit none
Use(Dim) # nx,ny
Use(Math_problem_size) # neqmx
Use(Share) # nxomit,nxc,nxleg,nxcore,geometry,ismpsym
Use(Xpoint_indices) # ixpt1,ixpt2,iysptrx1,iysptrx2,iysptrx
Use(RZ_grid_info) # rm,zm,psi,br,bz,bpol,bphi,b
Expand All @@ -456,6 +457,7 @@ logical function tstguardc (ix, iy)
Use(UEpar) # thetar
Use(Phyvar) # pi
Use(Bfield) # b0old
Use(Lsode) # iprint
Use(Npes_mpi) # mype
Use(Comgeo) # area_core
* -- local scalars --
Expand Down Expand Up @@ -487,7 +489,7 @@ c write(6,*) "Calling flxrun in globalmesh."
else
fname = trim(GridFileName)
call readgrid(fname, runid)
write(*,*) 'Read file "', fname, '" with runid: ', runid
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) 'Read file "', fname, '" with runid: ', runid
write(*,*)
endif
elseif (mhdgeo .eq. 2) then
Expand All @@ -497,23 +499,23 @@ call readgrid(fname, runid)
else
fname = trim(GridFileName)
call readgrid(fname, runid)
write(*,*) 'Read file "', fname, '" with runid: ', runid
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) 'Read file "', fname, '" with runid: ', runid
write(*,*)
endif
elseif (mhdgeo .eq. 0) then
call idealgrd
write(*,*) '**** mhdgeo=0: cylindrical grid generated *****'
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) '**** mhdgeo=0: cylindrical grid generated *****'
elseif (mhdgeo .eq. -1) then
call idealgrd
write(*,*) '**** mhdgeo=-1: cartesian grid generated *****'
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) '**** mhdgeo=-1: cartesian grid generated *****'
elseif (mhdgeo .eq. -2) then
call mirrorgrd
write(*,*) '**** mhdgeo=-2: mag mirror grid generated *****'
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) '**** mhdgeo=-2: mag mirror grid generated *****'
else
write(*,*) '**** mhdgeo < -1: reading grid from file *****'
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) '**** mhdgeo < -1: reading grid from file *****'
fname = trim(GridFileName)
call readgrid(fname, runid)
write(*,*) 'Read file "', fname, '" with runid: ', runid
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) 'Read file "', fname, '" with runid: ', runid
write(*,*)
endif

Expand Down Expand Up @@ -635,6 +637,7 @@ call s2copy (nx+2,ny+2,psi(0,0,ij),1,nx+2,psig(0,0,ij),1,nx+2)
Use(Indices_domain_dcl) # ixmnbcl,ixmxbcl
Use(Math_problem_size) # neqmx
Use(Npes_mpi) # mype
Use(Lsode) # iprint

* -- local scalars --
integer nj, iu, ik, ij, jx, iysi, iyso, iyp1, ix_last_core_cell,
Expand Down Expand Up @@ -680,7 +683,7 @@ call remark('*** WARNING: ismmon.ne.0 BUT isnonog=0 ****')
else
fname = trim(GridFileName)
call readgrid(fname, runid)
write(*,*) 'Read file "', fname, '" with runid: ', runid
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) 'Read file "', fname, '" with runid: ', runid
c ... now that the grid is read in, we can manipulate dnull for nxomit>0
if (geometry=="dnull" .and. nxpt==2) then
if (nxomit >= ixlb(2)) then
Expand All @@ -702,7 +705,7 @@ call remark("*** nxomit>0: do outer quad as single-null")
else
fname = trim(GridFileName)
call readgrid(fname, runid)
write(*,*) 'Read file "', fname, '" with runid: ', runid
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) 'Read file "', fname, '" with runid: ', runid
write(*,*)
endif
elseif (mhdgeo .eq. 0) then
Expand All @@ -718,7 +721,7 @@ call readgrid(fname, runid)
write(*,*) '**** mhdgeo < -1: reading grid from file *****'
fname = trim(GridFileName)
call readgrid(fname, runid)
write(*,*) 'Read file "', fname, '" with runid: ', runid
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) 'Read file "', fname, '" with runid: ', runid
write(*,*)
endif

Expand Down
5 changes: 3 additions & 2 deletions bbb/oderhs.m
Original file line number Diff line number Diff line change
Expand Up @@ -8438,8 +8438,6 @@ cc real(Size4) ranf
c ... Pause from BASIS if a ctrl_c is typed
call ruthere
c ... Count Jacobian evaluations, both for total and for this case
ijactot = ijactot + 1 #note: ijactot set 0 in exmain if icntnunk=0
ijac(ig) = ijac(ig) + 1
if (svrpkg.eq.'nksol') write(*,*) ' Updating Jacobian, npe = ',
Expand Down Expand Up @@ -8593,6 +8591,9 @@ ccc call pandf1 (xc, yc, iv, neq, t, yl, wk)
c sparse row format.
call csrcsc (neq, 1, 1, rcsc, icsc, jcsc, jac, ja, ia)
c ... Count Jacobian evaluations, both for total and for this case
ijactot = ijactot + 1 #note: ijactot set 0 in exmain if icntnunk=0
c ... Accumulate cpu time spent here.
if (istimingon .eq. 1) ttjstor = ttjstor + gettime(sec4) - tsjstor
return
Expand Down
2 changes: 1 addition & 1 deletion bbb/odesetup.m
Original file line number Diff line number Diff line change
Expand Up @@ -6492,7 +6492,7 @@ c_mpi call MPI_BCAST(area_core,1,MPI_DOUBLE_PRECISION,0,uedgeComm,ierr)
Use(Npes_mpi) # npes,mype,ispmion
Use(UEint) # isallloc
Use(Rccoef) # isoutwall
Use(Coefeq) # jhswitch, oldseec
Use(Coefeq) # oldseec, override
c_mpi Use(MpiVars) #module defined in com/mpivarsmod.F.in

integer ifake #forces Forthon scripts to put implicit none above here
Expand Down
1 change: 1 addition & 0 deletions bbb/odesolve.m
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@
Use(Compla) # ni,up,vy,te,ti,phi,zeff,nil,upl,tel,til,ngl,phil
Use(Grid) # ngrid,ig,imeth,ijac,iyld,yldmax
Use(Stat)
Use(Ident_vars) # exmain_evals
Use(Ynorm) # suscal,sfscal
Use(Ident_vars) # exmain_evals
Use(Oldpla)
Expand Down
2 changes: 1 addition & 1 deletion grd/grddriv.m
Original file line number Diff line number Diff line change
Expand Up @@ -41,9 +41,9 @@ call gallot("Argfc",0) #uses npts,nconst,nwdim,niwdim

call ingrd
call grdgen
write(*,*) '***** Grid generation has been completed'
call writeue

write(*,*) '***** Grid generation has been completed'

return
end
Expand Down
11 changes: 10 additions & 1 deletion grd/grdread.m
Original file line number Diff line number Diff line change
Expand Up @@ -153,6 +153,9 @@ subroutine readgridpars(fname, runid)
real simagxs_tmp, sibdrys_tmp
external freeus,remark,xerrab,gallot,rdgrid

if (isgriduehdf5 .eq. 1) then
call parsestr('import uedge.gridue as gue;gue.read_gridpars()')
else
c Read mesh parameters from a UEDGE code grid data file
simagxs_tmp=0
sibdrys_tmp=0
Expand Down Expand Up @@ -185,6 +188,7 @@ call xerrab("**** requested grid data file not found")
close (nuno)

1999 format(5i4)
endif

return
end
Expand All @@ -193,14 +197,18 @@ call xerrab("**** requested grid data file not found")

subroutine readgrid(fname, runid)
implicit none
Use(Share) # geometry
Use(Share) # geometry, isgriduehdf5
Use(Dim) # nxm,nym
Use(Xpoint_indices) # ixlb,ixpt1,ixmdp,ixpt2,ixrb,iysptrx1,iysptrx2
character*(*) fname, runid
integer nuno,ios
real simagxs_tmp, sibdrys_tmp
external freeus,remark,xerrab,gallot,rdgrid

if (isgriduehdf5 .eq. 1) then
call parsestr('import uedge.gridue as gue;gue.read_gridue()')
else

c Read a UEDGE code grid data file
simagxs_tmp=0
sibdrys_tmp=0
Expand Down Expand Up @@ -234,6 +242,7 @@ call gallot("RZ_grid_info",0)
call rdgrid(nuno, runid)

close (nuno)
endif # end isgriduehdf5 check

return
end
Expand Down
21 changes: 17 additions & 4 deletions grd/grdwrit.m
Original file line number Diff line number Diff line change
Expand Up @@ -150,7 +150,11 @@ call mapdnbot2dnull(ixpt1t,ixtopt,ixpt2t,nxmt,iysptrxt,nymt)
call add_guardc_tp
call magnetics(0,nxm+1,1,nym)
call symmetrize_magnetics
call writednf (fname, runidarg)
if (isgriduehdf5 .eq. 1) then
call parsestr('import uedge.gridue as gue;gue.write_gridue()')
else
call writednf (fname, runidarg)
endif
else
c write the outboard half of the full double null geometry,
c excluding the PLANET guard cells near the x-points.
Expand Down Expand Up @@ -426,7 +430,11 @@ call xerrab("*** ix indexing error in subroutine wrdndata ***")
call magnetics(1,nxm,1,nym)
# Finally, write out the data --
call writedata (fname, runidarg)
if (isgriduehdf5 .eq. 1) then
call parsestr('import uedge.gridue as gue;gue.write_gridue()')
else
call writedata (fname, runidarg)
endif
return
end
Expand All @@ -441,7 +449,7 @@ subroutine writesn (fname, runidarg)
Use(Dimensions)
Use(Inmesh)
Use(Linkco)
Use(Share) # nxxpt
Use(Share) # nxxpt, isgriduehdf5
character*(*) fname, runidarg
external gallot, wrsndata
Expand Down Expand Up @@ -579,7 +587,12 @@ call xerrab("*** ix indexing error in subroutine wrsndata ***")
call magnetics(ixmin,nxm,1,nym)
# Finally, write out the data --
call writedata (fname, runidarg)
if (isgriduehdf5 .eq. 1) then
call parsestr('import uedge.gridue as gue;gue.write_gridue()')
else
call writedata (fname, runidarg)
endif
return
end
Expand Down
Loading

0 comments on commit a4ea519

Please sign in to comment.