Skip to content

Commit

Permalink
debugging of analyt
Browse files Browse the repository at this point in the history
  • Loading branch information
jons-pf committed Oct 23, 2024
1 parent b0bf098 commit fedd4cb
Show file tree
Hide file tree
Showing 3 changed files with 26 additions and 14 deletions.
23 changes: 14 additions & 9 deletions Sources/Initialization_Cleanup/allocate_funct3d.f
Original file line number Diff line number Diff line change
Expand Up @@ -50,13 +50,13 @@ SUBROUTINE allocate_funct3d_par
ALLOCATE (pextra1(nznt,ns,0:1), stat=istat1)
IF (istat1.ne.0) STOP 'allocation error #3 in allocate_funct3d'
pextra1=0

IF (lasym) THEN
ALLOCATE (pextra2(nznt,ns,0:1),
ALLOCATE (pextra2(nznt,ns,0:1),
& pextra3(nznt,ns,0:1),
& pextra4(nznt,ns,0:1),stat=istat1)
ELSE
ALLOCATE (pextra2(nznt,ns,1),
ALLOCATE (pextra2(nznt,ns,1),
& pextra3(nznt,ns,1),
& pextra4(nznt,ns,1),stat=istat1)
END IF
Expand All @@ -70,15 +70,15 @@ SUBROUTINE allocate_funct3d_par
parmn_e => parmn(:,:,0)
parmn_o => parmn(:,:,1)
parmn = zero

pazmn_e => pazmn(:,:,0)
pazmn_o => pazmn(:,:,1)
pazmn = zero

pbrmn_e => pbrmn(:,:,0)
pbrmn_o => pbrmn(:,:,1)
pbrmn = zero

pbzmn_e => pbzmn(:,:,0)
pbzmn_o => pbzmn(:,:,1)
pbzmn = zero
Expand Down Expand Up @@ -137,16 +137,21 @@ SUBROUTINE allocate_funct3d_par
STOP 'allocation error #2 in allocate_funct3d'
END IF
brv=0; bphiv=0; bzv=0; bsqvac=0

allocate(all_tlp(0:mf+nf, nuv3), all_tlm(0:mf+nf, nuv3), &
& all_slp(0:mf+nf, nuv3), all_slm(0:mf+nf, nuv3), &
& stat=istat1)
IF (istat1 .ne. 0) STOP 'Allocation error for debugging analyt'
END IF

ALLOCATE (extra1(ndim,0:1), stat=istat1)
IF (istat1.ne.0) THEN
STOP 'allocation error #3 in allocate_funct3d'
END IF
extra1=0

IF (lasym) THEN
ALLOCATE (extra2(ndim,0:1), extra3(ndim,0:1),
ALLOCATE (extra2(ndim,0:1), extra3(ndim,0:1),
1 extra4(ndim,0:1),stat=istat1)
ELSE
ALLOCATE (extra2(ndim,1), extra3(ndim,1), extra4(ndim,1),
Expand Down Expand Up @@ -246,9 +251,9 @@ SUBROUTINE allocate_funct3d
STOP 'allocation error #3 in allocate_funct3d'
END IF
extra1=0

IF (lasym) THEN
ALLOCATE (extra2(ndim,0:1), extra3(ndim,0:1),
ALLOCATE (extra2(ndim,0:1), extra3(ndim,0:1),
& extra4(ndim,0:1),stat=istat1)
ELSE
ALLOCATE (extra2(ndim,1), extra3(ndim,1), extra4(ndim,1),
Expand Down
7 changes: 4 additions & 3 deletions Sources/NESTOR_vacuum/precal.f
Original file line number Diff line number Diff line change
Expand Up @@ -208,9 +208,10 @@ SUBROUTINE precal (wint)
!
DO m = 1,mf
DO n = 1,nf
cmns(0:mf+nf,m,n) = p5*alp*(cmn(0:mf+nf,m,n) +
1 cmn(0:mf+nf,m-1,n) + cmn(0:mf+nf,m,n-1) +
2 cmn(0:mf+nf,m-1,n-1))
cmns(0:mf+nf,m,n) = p5*alp*(cmn(0:mf+nf,m ,n ) +
1 cmn(0:mf+nf,m-1,n ) +
2 cmn(0:mf+nf,m ,n-1) +
3 cmn(0:mf+nf,m-1,n-1))
END DO
END DO
cmns(0:mf+nf,1:mf,0) = (p5*alp)*(cmn(0:mf+nf,1:mf,0)
Expand Down
10 changes: 8 additions & 2 deletions Sources/NESTOR_vacuum/vacmod.f
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ MODULE vacmod
USE vmec_input, ONLY: lasym
USE vmec_params, ONLY: signgs
USE vparams, ONLY: zero, one, c2p0, cp5
USE mgrid_mod, ONLY: nr0b, np0b, nz0b,
USE mgrid_mod, ONLY: nr0b, np0b, nz0b,
1 rminb, zminb, rmaxb, zmaxb, delrb, delzb
IMPLICIT NONE
C-----------------------------------------------
Expand All @@ -22,8 +22,14 @@ MODULE vacmod
3 guu_b, guv_b, gvv_b, rzb2, rcosuv, rsinuv,
5 bredge, bpedge, bzedge
INTEGER, ALLOCATABLE :: ipiv(:)
REAL(rprec), DIMENSION(:), ALLOCATABLE :: raxis_nestor,
REAL(rprec), DIMENSION(:), ALLOCATABLE :: raxis_nestor,
1 zaxis_nestor
REAL(rprec) :: bsubvvac, pi2,
2 pi3, pi4, alp, alu, alv, alvp, onp, onp2

real(rprec), dimension(:,:), allocatable :: all_tlp
real(rprec), dimension(:,:), allocatable :: all_tlm
real(rprec), dimension(:,:), allocatable :: all_slp
real(rprec), dimension(:,:), allocatable :: all_slm

END MODULE vacmod

0 comments on commit fedd4cb

Please sign in to comment.