Skip to content

Commit

Permalink
Merge branch 'develop' into Tg_for_test
Browse files Browse the repository at this point in the history
  • Loading branch information
holm10 authored Jan 9, 2024
2 parents 399fb95 + 94e87d0 commit 47b0cc2
Show file tree
Hide file tree
Showing 78 changed files with 979 additions and 25,625 deletions.
2 changes: 2 additions & 0 deletions .gitignore
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
*.pyc
*.F
a.out
*/build/
build/
.idea/
Expand All @@ -16,3 +17,4 @@ uedge.egg-info
*.egg
*.c
*.f
pyscripts/__version__.py
2 changes: 1 addition & 1 deletion api/fimp.m
Original file line number Diff line number Diff line change
Expand Up @@ -267,7 +267,7 @@ subroutine readmc(nzdf,mcfilename)
character*256 fname
Use(Multicharge)
Use(Math_problem_size) # neqmx
Use(Lsode) # iprint
Use(Flags) # iprint
Use(Impdata) #apidir
c ... Function:
Expand Down
2 changes: 1 addition & 1 deletion api/sputt.m
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ SUBROUTINE SYLD96(MATT,MATP,CION,CIZB,CRMB)

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

real ETH(7,12), ETF(7,12), Q(7,12), EBD(12)
LOGICAL IDATA(7,12)
Expand Down
4 changes: 2 additions & 2 deletions bbb/bbb.v
Original file line number Diff line number Diff line change
Expand Up @@ -1125,7 +1125,7 @@ mfnksol integer /-3/#nksol method flag; =1 means dogleg strategy,
#=3 means linesearch with GMRES method.
#=4 full direct solve by RSmirnov;set premeth=banded
#negative mfnksol ignores global constaints
iprint integer /1/ #nksol optional statistics flag.
xiprint integer /1/ #nksol optional statistics flag.
#=0 means no optional statistics are printed.
#=1 means iteration count, norm of F(u) and
# no. of F evaluations are printed.
Expand Down Expand Up @@ -3889,7 +3889,7 @@ yielh(imx+1) _real
yielz(imx+1,lnst+1) _real

***** Ident_vars:
uedge_ver character*80 /'$Name: 8.0.4.0$'/
uedge_ver character*80 /'$Name: 8.0.5-beta.3$'/
uedge_date character*80 /'Version date in README_Uedge_vers in dir uedge'/
session_id integer /0/ # Identifier for use with uetools
max_session_id integer /0/ # Identifier for max allocated runs, use with uetools
Expand Down
26 changes: 13 additions & 13 deletions bbb/geometry.m
Original file line number Diff line number Diff line change
Expand Up @@ -457,7 +457,7 @@ logical function tstguardc (ix, iy)
Use(UEpar) # thetar
Use(Phyvar) # pi
Use(Bfield) # b0old
Use(Lsode) # iprint
Use(Flags) # iprint
Use(Npes_mpi) # mype
Use(Comgeo) # area_core
* -- local scalars --
Expand Down Expand Up @@ -490,17 +490,17 @@ c write(6,*) "Calling flxrun in globalmesh."
fname = trim(GridFileName)
call readgrid(fname, runid)
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) 'Read file "', fname, '" with runid: ', runid
write(*,*)
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*)
endif
elseif (mhdgeo .eq. 2) then
if (gengrid == 1) then
call torangrd
write(*,*) '**** mhdgeo=2: Circ toroidal annulus generated *****'
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) '**** mhdgeo=2: Circ toroidal annulus generated *****'
else
fname = trim(GridFileName)
call readgrid(fname, runid)
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) 'Read file "', fname, '" with runid: ', runid
write(*,*)
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*)
endif
elseif (mhdgeo .eq. 0) then
call idealgrd
Expand All @@ -516,7 +516,7 @@ call readgrid(fname, runid)
fname = trim(GridFileName)
call readgrid(fname, runid)
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) 'Read file "', fname, '" with runid: ', runid
write(*,*)
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*)
endif

c... Reset separatrix index if nyomitmx > 0
Expand Down Expand Up @@ -637,7 +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
Use(Flags) # iprint

* -- local scalars --
integer nj, iu, ik, ij, jx, iysi, iyso, iyp1, ix_last_core_cell,
Expand Down Expand Up @@ -701,28 +701,28 @@ call remark("*** nxomit>0: do outer quad as single-null")
elseif (mhdgeo .eq. 2) then
if (gengrid == 1) then
call torangrd
write(*,*) '*** mhdgeo=2: Circ toroidal annulus ***'
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) '*** mhdgeo=2: Circ toroidal annulus ***'
else
fname = trim(GridFileName)
call readgrid(fname, runid)
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) 'Read file "', fname, '" with runid: ', runid
write(*,*)
if (iprint*(1-isgriduehdf5) .ne. 0) 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)
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*) 'Read file "', fname, '" with runid: ', runid
write(*,*)
if (iprint*(1-isgriduehdf5) .ne. 0) write(*,*)
endif

c... Reset separatrix index if nyomitmx > 0
Expand Down
3 changes: 2 additions & 1 deletion bbb/oderhs.m
Original file line number Diff line number Diff line change
Expand Up @@ -8542,6 +8542,7 @@ integer ia(neq+1) # pointers to beginning of each row in jac,ja
Use(Time_dep_nwt) # nufak,dtreal,ylodt,dtuse
Use(Selec) # yinc
Use(Jacaux) # ExtendedJacPhi
Use(Flags) # ExtendedJacPhi

c ... Functions:
logical tstguardc
Expand All @@ -8563,7 +8564,7 @@ cc real(Size4) ranf

ijac(ig) = ijac(ig) + 1

if (svrpkg.eq.'nksol') write(*,*) ' Updating Jacobian, npe = ',
if ((svrpkg.eq.'nksol') .and. (iprint .ne. 0)) write(*,*) ' Updating Jacobian, npe = ',
. ijac(ig)

c ... Set up diagnostic arrays for debugging
Expand Down
5 changes: 3 additions & 2 deletions bbb/odesetup.m
Original file line number Diff line number Diff line change
Expand Up @@ -6493,6 +6493,7 @@ c_mpi call MPI_BCAST(area_core,1,MPI_DOUBLE_PRECISION,0,uedgeComm,ierr)
Use(UEint) # isallloc
Use(Rccoef) # isoutwall
Use(Coefeq) # oldseec, override, cftiexclg
Use(Flags) # iprint
c_mpi Use(MpiVars) #module defined in com/mpivarsmod.F.in

integer ifake #forces Forthon scripts to put implicit none above here
Expand All @@ -6517,7 +6518,7 @@ c_mpi call MPI_BARRIER(uedgeComm, ierr)
ifexmain = 1
call allocate
ifexmain = 0
if (icall == 0) write(*,*) 'UEDGE ',uedge_ver
if ((icall == 0) .and. (iprint .ne. 0)) write(*,*) 'UEDGE ',uedge_ver
icall = 1
elseif (ismpion.eq.1 .and. icall==0) then
call init_pll
Expand Down Expand Up @@ -6647,7 +6648,7 @@ call gchange("Interp",0)
call comp_vertex_vals # gen plasma/neut values at rm,zm(,,4)
endif
endif
write(6,*) "Interpolants created; mype =", mype
if (iprint .ne. 0) write(6,*) "Interpolants created; mype =", mype
endif

100 continue
Expand Down
2 changes: 2 additions & 0 deletions bbb/odesolve.m
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@

Use(Jacreorder) # ireorder
Use(Jacobian) # nnzmx
Use(Flags) # iprint

c Diagnostic data
Use(Comgeo) # gxf,sx
Expand Down Expand Up @@ -603,6 +604,7 @@ c_mpi write(6,1267) iopt(4), iopt(11), iopt(5),
Use(Lsode)
Use(Npes_mpi)
Use(Parallv)
Use(Flags)
C diagnostic data
Use(Indices_domain_dcl)
c_mpi Use(MpiVars) #module defined in com/mpivarsmod.F.in
Expand Down
4 changes: 4 additions & 0 deletions com/com.v
Original file line number Diff line number Diff line change
Expand Up @@ -696,3 +696,7 @@ tanh_multi(i:integer,a:real,j:integer,b:real,fname:string,d:real) subroutine
# in b psi values at eval pts
# in fname the filename
# out d values of fit

***** Flags:
# Common flags used by UEDGE
iprint integer /1/ # Flag controlling whether to be verbose or not
6 changes: 4 additions & 2 deletions grd/grdread.m
Original file line number Diff line number Diff line change
Expand Up @@ -148,6 +148,7 @@ subroutine readgridpars(fname, runid)
Use(Share) # geometry
Use(Dim) # nxm,nym
Use(Xpoint_indices) # ixlb,ixpt1,ixmdp,ixpt2,ixrb,iysptrx1,iysptrx2
Use(Flags) # iprint
character*(*) fname, runid
integer nuno,ios
real simagxs_tmp, sibdrys_tmp
Expand All @@ -160,7 +161,7 @@ subroutine readgridpars(fname, runid)
simagxs_tmp=0
sibdrys_tmp=0
call freeus (nuno)
write(*,*) 'Reading grid from file:',trim(fname)
if (iprint .ne. 0) write(*,*) 'Reading grid from file:',trim(fname)
open (nuno, file=trim(fname), form='formatted', iostat=ios,
& status='old')
if (ios .ne. 0) then
Expand Down Expand Up @@ -200,6 +201,7 @@ subroutine readgrid(fname, runid)
Use(Share) # geometry, isgriduehdf5
Use(Dim) # nxm,nym
Use(Xpoint_indices) # ixlb,ixpt1,ixmdp,ixpt2,ixrb,iysptrx1,iysptrx2
Use(Flags) # iprint
character*(*) fname, runid
integer nuno,ios
real simagxs_tmp, sibdrys_tmp
Expand All @@ -213,7 +215,7 @@ subroutine readgrid(fname, runid)
simagxs_tmp=0
sibdrys_tmp=0
call freeus (nuno)
write(*,*) 'Reading grid from file:',trim(fname)
if (iprint .ne. 0) write(*,*) 'Reading grid from file:',trim(fname)
open (nuno, file=trim(fname), form='formatted', iostat=ios,
& status='old')
if (ios .ne. 0) then
Expand Down
1 change: 0 additions & 1 deletion pyexamples/empty-file

This file was deleted.

5 changes: 5 additions & 0 deletions pyexamples/input_example/conftest.py
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
import pytest

@pytest.fixture(autouse=True)
def change_test_dir(request, monkeypatch):
monkeypatch.chdir(request.fspath.dirname)
Loading

0 comments on commit 47b0cc2

Please sign in to comment.