69 s lxb,lyb,nxb,nyb,nncut,nxcut,nycut,
70 s nniso,nxiso,nyiso,br,bz,
71 s lx,ly,nxl,nyl,ierr,leir)
73 u gridman_unit,gridman_dbg,gridman_check
77 INTRINSIC floor,mod,abs
82 INTEGER(GRIDMAN_SP),
INTENT(IN) :: LXB
84 INTEGER(GRIDMAN_SP),
INTENT(IN) :: LYB
86 INTEGER(GRIDMAN_SP),
INTENT(IN) :: NXB
88 INTEGER(GRIDMAN_SP),
INTENT(IN) :: NYB
90 INTEGER(GRIDMAN_SP),
INTENT(IN) :: NNCUT
92 INTEGER(GRIDMAN_SP),
INTENT(IN) :: NNISO
93 INTEGER(GRIDMAN_SP),
INTENT(IN) :: NXCUT30(2,nncut)
94 INTEGER(GRIDMAN_SP),
INTENT(IN) :: NYCUT30(2,nncut)
95 INTEGER(GRIDMAN_SP),
INTENT(IN) :: NXISO30(2,nniso)
96 INTEGER(GRIDMAN_SP),
INTENT(IN) :: NYISO30(2,nniso)
98 INTEGER(GRIDMAN_SP),
INTENT(IN) :: NXCUT(nncut)
100 INTEGER(GRIDMAN_SP),
INTENT(IN) :: NYCUT(nncut)
102 INTEGER(GRIDMAN_SP),
INTENT(IN) :: NXISO(nniso)
104 INTEGER(GRIDMAN_SP),
INTENT(IN) :: NYISO(nniso)
106 REAL(GRIDMAN_DP) :: BR(lxb:nxb,lyb:nyb,4)
108 REAL(GRIDMAN_DP) :: BZ(lxb:nxb,lyb:nyb,4)
110 INTEGER(GRIDMAN_SP),
INTENT(IN) :: LX
112 INTEGER(GRIDMAN_SP),
INTENT(IN) :: LY
114 INTEGER(GRIDMAN_SP),
INTENT(IN) :: NXL
116 INTEGER(GRIDMAN_SP),
INTENT(IN) :: NYL
118 INTEGER,
INTENT(OUT) :: IERR
123 LOGICAL,
OPTIONAL :: LEIR
125 INTEGER(GRIDMAN_SP) :: NX,NY,NCELLS,NPOL,NRAD,NEDGES,NPOINTS,NBND,
126 i icell,ix,iy,ic,ip,ie,m,iedge,
127 i ipoint,icell1,icell2,ix1,ix2,iy1,iy2,
130 REAL(GRIDMAN_DP) :: X1,X2,Y1,Y2
131 LOGICAL :: LFORT30,LFREEEDGES
139 entry gridman_carre2grid_fort30(grid,lxb,lyb,nxb,nyb,nncut,
140 s nxcut30,nycut30,nniso,
141 s nxiso30,nyiso30,br,bz,
142 s lx,ly,nxl,nyl,ierr,leir)
149 w
WRITE(gridman_unit,*)
"Starting GRIDMAN_CARRE2GRID"
153 IF(nxl.LT.lx+1.OR.nyl.LT.ly+1)
THEN
155 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
156 w
"wrong dimensions, LX, LY, NX, NY ",
166 IF(ix1.LT.lx.OR.ix2.LT.lx.OR.ix1.GT.nxl.OR.ix2.GT.nxl.OR.
167 f nycut30(2,ic).LT.nycut30(1,ic).OR.nycut30(2,ic).GT.nyl)
THEN
169 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
170 o
"incorrect parameters of vertical cuts"
171 WRITE(gridman_unit,*)
" NXCUT1 ", nxcut30(1,:)
172 WRITE(gridman_unit,*)
" NXCUT2 ", nxcut30(2,:)
173 WRITE(gridman_unit,*)
" NYCUT1 ", nycut30(1,:)
174 WRITE(gridman_unit,*)
" NYCUT2 ", nycut30(2,:)
175 WRITE(gridman_unit,*)
" MIN(IX), MAX(IX), MIN(IY), MAX(IY) ",
184 IF(ix1.LT.lx-1.OR.ix2.LT.lx-1.OR.ix1.GT.nxl.OR.ix2.GT.nxl.OR.
185 f nycut(ic).LT.nycut(ic).OR.nycut(ic).GT.nyl)
THEN
187 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
188 o
"incorrect parameters of vertical cuts"
189 WRITE(gridman_unit,*)
" NXCUT ", nxcut(1:nncut)
190 WRITE(gridman_unit,*)
" NYCUT ", nycut(1:nncut)
191 WRITE(gridman_unit,*)
" MIN(IX), MAX(IX), MIN(IY), MAX(IY) ",
204 npoints=(nx+1)*(ny+1)
210 IF(ierr.NE.0)
GOTO 1000
213 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
214 w
"cannot allocate temporar 1st edge index"
217 grid%EDGEINDEX(1)%INDEXES(0,1)=1
218 grid%EDGEINDEX(1)%INDEXES(1,1)=1
221 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
222 w
"cannot allocate index of poloidal edges"
227 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
228 w
"cannot allocate index of radial edges"
233 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
234 w
"cannot allocate index of cells"
286 grid%CELLS(1,iedge)=iedge
287 grid%CELLS(2,iedge)=0
288 grid%POINTS(1,iedge)=iedge
289 grid%POINTS(2,iedge)=grid%POINTS(1,iedge)+1
290 grid%EDGEINDEX(2)%INDEXES(0,iedge)=iedge
291 grid%EDGEINDEX(2)%INDEXES(1,iedge)=ix
292 grid%EDGEINDEX(2)%INDEXES(2,iedge)=ly-1
297 grid%CELLS(1,iedge)=iedge-nx
298 grid%CELLS(2,iedge)=iedge
299 grid%POINTS(1,iedge)=iedge+iy-ly
300 grid%POINTS(2,iedge)=grid%POINTS(1,iedge)+1
301 grid%EDGEINDEX(2)%INDEXES(0,iedge)=iedge
302 grid%EDGEINDEX(2)%INDEXES(1,iedge)=ix
303 grid%EDGEINDEX(2)%INDEXES(2,iedge)=iy-1
308 grid%CELLS(1,iedge)=iedge-nx
309 grid%CELLS(2,iedge)=0
310 grid%POINTS(1,iedge)=iedge+ny
311 grid%POINTS(2,iedge)=grid%POINTS(1,iedge)+1
312 grid%EDGEINDEX(2)%INDEXES(0,iedge)=iedge
313 grid%EDGEINDEX(2)%INDEXES(1,iedge)=ix
314 grid%EDGEINDEX(2)%INDEXES(2,iedge)=nyl
318 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
319 o
"specification of CELLS is incorrect"
320 WRITE(gridman_unit,*)
" IEDGE, M, NY, NX, ",
338 grid%CELLS(1,iedge)=iedge-m-iy+ly
339 grid%CELLS(2,iedge)=0
340 grid%POINTS(1,iedge)=iedge-m
341 grid%POINTS(2,iedge)=grid%POINTS(1,iedge)+nx+1
343 grid%EDGEINDEX(3)%INDEXES(0,ie)=iedge
344 grid%EDGEINDEX(3)%INDEXES(1,ie)=lx-1
345 grid%EDGEINDEX(3)%INDEXES(2,ie)=iy
348 grid%CELLS(1,iedge)=iedge-m-(iy-ly+1)
349 grid%CELLS(2,iedge)=iedge-m-(iy-ly+1)+1
350 grid%POINTS(1,iedge)=iedge-m
351 grid%POINTS(2,iedge)=grid%POINTS(1,iedge)+nx+1
353 grid%EDGEINDEX(3)%INDEXES(0,ie)=iedge
354 grid%EDGEINDEX(3)%INDEXES(1,ie)=ix-1
355 grid%EDGEINDEX(3)%INDEXES(2,ie)=iy
358 grid%CELLS(1,iedge)=iedge-m-(iy-ly+1)
359 grid%CELLS(2,iedge)=0
360 grid%POINTS(1,iedge)=iedge-m
361 grid%POINTS(2,iedge)=grid%POINTS(1,iedge)+nx+1
363 grid%EDGEINDEX(3)%INDEXES(0,ie)=iedge
364 grid%EDGEINDEX(3)%INDEXES(1,ie)=nxl
365 grid%EDGEINDEX(3)%INDEXES(2,ie)=iy
367 IF(iedge.NE.nedges)
THEN
369 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
370 o
"specification of CELLS is incorrect"
371 WRITE(gridman_unit,*)
" IEDGE, NEDGES, NY, NX ",
372 o iedge, nedges, ny, nx
397 grid%X(1,ipoint)=br(ix,iy,4)
398 grid%X(2,ipoint)=bz(ix,iy,4)
401 grid%X(1,ipoint)=br(nxl,iy,1)
402 grid%X(2,ipoint)=bz(nxl,iy,1)
406 grid%X(1,ipoint)=br(ix,nyl,3)
407 grid%X(2,ipoint)=bz(ix,nyl,3)
410 grid%X(1,ipoint)=br(nxl,nyl,2)
411 grid%X(2,ipoint)=bz(nxl,nyl,2)
412 IF(ipoint.NE.npoints)
THEN
414 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
415 o
"specification of points is incorrect"
416 WRITE(gridman_unit,*)
" IPOINT, NPOINTS, NY, NX, ",
417 o ipoint, npoints, ny, nx
424 icell=ix-lx+1+nx*(iy-ly)
425 grid%CELLINDEX(1)%INDEXES(0,icell)=icell
426 grid%CELLINDEX(1)%INDEXES(1,icell)=ix
427 grid%CELLINDEX(1)%INDEXES(2,icell)=iy
449 iy1=max(nycut30(1,ic),ly)
461 icell2=ix2-1-lx+1+nx*(iy-ly)
462 iedge=icell2+iy-ly+m+1
463 grid%CELLS(1,iedge)=0
464 grid%CELLS(2,iedge)=0
470 w
WRITE(gridman_unit,*)
" IC, IX1, IX2, IY1, IY2 ",
483 icell1=ix1-lx+1+nx*(iy-ly)
484 icell2=ix2-lx+1+nx*(iy-ly)
486 ipoint1=grid%POINTS(1,iedge)
487 ipoint2=grid%POINTS(2,iedge)
489 grid%CELLS(1,iedge)=icell1
490 grid%CELLS(2,iedge)=icell2
496 IF(abs(x1-grid%X(1,ipoint1)).GT.
498 f abs(y1-grid%X(2,ipoint1)).GT.
499 f
gridman_tol*(abs(y1)+abs(grid%X(2,ipoint1))) .OR.
500 f abs(x2-grid%X(1,ipoint2)).GT.
502 f abs(y2-grid%X(2,ipoint2)).GT.
503 f
gridman_tol*(abs(y2)+abs(grid%X(2,ipoint2))) )
THEN
505 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
506 o
"coordinates at the cut do not match each over"
507 WRITE(gridman_unit,*)
"POINT1: X1,Y1 vs. X2,Y2 ",x1,y1,
508 w grid%X(1,ipoint1),grid%X(2,ipoint1)
509 WRITE(gridman_unit,*)
"POINT2: X1,Y1 vs. X2,Y2 ",x2,y2,
510 w grid%X(1,ipoint2),grid%X(2,ipoint2)
511 WRITE(gridman_unit,*)
"IX1, IX2, IY ",ix1,ix2,iy
515 grid%EDGEINDEX(3)%INDEXES(1,iedge-npol)=ix1
518 grid%POINTS(2,iedge)=ipoint1
522 ipoint=grid%POINTS(2,iedge)
528 f abs(y1-y2).GT.
gridman_tol*(abs(x1)+abs(x2)))
THEN
530 WRITE(gridman_unit,*)
"WARNING from GRIDMAN_CARRE2GRID: ",
531 o
"could not identtify X-point"
532 WRITE(gridman_unit,*)
"POINT1: X1,Y1 ",x1,y1
533 WRITE(gridman_unit,*)
"POINT2: X2,Y2 ",x2,y2
535 grid%POINTS(2,iedge)=ipoint2
552 iedge=icell1+m+iy-ly+1
553 grid%POINTS(1,iedge)=ipoint2
555 grid%POINTS(2,iedge)=ipoint2
559 grid%POINTS(1,iedge)=ipoint2
563 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
564 o
"NYCUT(1)>MIN(IY) is not implemented"
565 WRITE(gridman_unit,*)
" NYCUT(1) ",nycut(1)
572 CALL eliminate_free_edges(ierr)
573 IF(ierr.NE.0)
GOTO 2000
580 CALL eliminate_isolated_cells(ierr)
581 IF(ierr.NE.0)
GOTO 2000
587 CALL assign_surface_markers(ierr)
588 IF(ierr.NE.0)
GOTO 2000
593 IF(
PRESENT(leir))
THEN
597 ix1=nxcut30(1,ic)+ic-1
601 DO icell=1,grid%CELLINDEX(1)%NELEMENTS
602 ix=grid%CELLINDEX(1)%INDEXES(1,icell)
603 IF(ix.GT.ix1) grid%CELLINDEX(1)%INDEXES(1,icell)=ix+1
608 ix1=nxiso30(1,ic)+ic+nncut-2
610 ix1=nxiso(ic)+ic+nncut-2
612 DO icell=1,grid%CELLINDEX(1)%NELEMENTS
613 ix=grid%CELLINDEX(1)%INDEXES(1,icell)
614 IF(ix.GT.ix1) grid%CELLINDEX(1)%INDEXES(1,icell)=ix+1
621 grid%UNIT2SI=1.0_gridman_dp
624 grid%DESCRIPTION=
'CARRE grid (B2 plasma grid)'
625 grid%CELLINDEX(1)%DESCRIPTION=
626 =
"Indexes IX, IY of the plasma grid cells"
627 grid%CELLINDEX(1)%COLUMNS(1)=
"CARRE_CELL_IX"
628 grid%CELLINDEX(1)%COLUMNS(2)=
"CARRE_CELL_IY"
630 grid%EDGEINDEX(1)%DESCRIPTION=
"Markers of grid boundaries:"
631 / //
" -1 is South, -2 is West, -3 is East, -4 is North"
632 grid%EDGEINDEX(1)%COLUMNS(1)=
"CARRE_EDGE_ITAG"
634 grid%EDGEINDEX(2)%DESCRIPTION=
635 =
"Indexes IX, IY of the poloidal edges of plasma grid"
636 grid%EDGEINDEX(2)%COLUMNS(1)=
"CARRE_POL_FACE_IX"
637 grid%EDGEINDEX(2)%COLUMNS(2)=
"CARRE_POL_FACE_IY"
639 grid%EDGEINDEX(3)%DESCRIPTION=
640 =
"Indexes IX, IY of the radial edges of plasma grid"
641 grid%EDGEINDEX(3)%COLUMNS(1)=
"CARRE_RAD_FACE_IX"
642 grid%EDGEINDEX(3)%COLUMNS(2)=
"CARRE_RAD_FACE_IY"
644 IF(gridman_check)
THEN
646 IF(res.NE.0.OR.ierr.GT.0)
THEN
648 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
649 w
"resulting grid object is incorrect"
654 w
WRITE(gridman_unit,*)
"GRIDMAN_CARRE2GRID finished"
657 1000
WRITE(gridman_unit,*)
"GRIDMAN_CARRE2GRID terminated"
664 SUBROUTINE eliminate_free_edges(IERR)
666 INTEGER,
INTENT(OUT) :: IERR
676 END SUBROUTINE eliminate_free_edges
679 SUBROUTINE eliminate_isolated_cells(IERR)
681 INTEGER,
INTENT(OUT) :: IERR
682 LOGICAL :: LTAKE(grid%ncells)
684 INTEGER(GRIDMAN_SP) :: ISO,ICELL,IX,IY
689 IF(nniso.LT.1)
RETURN
696 WRITE(gridman_unit,*)
" NXISO ",nxiso30(1,iso),nxiso30(2,iso)
697 WRITE(gridman_unit,*)
" NYISO ",nyiso30(1,iso),nyiso30(2,iso)
699 DO icell=1,grid%NCELLS
700 ix=grid%CELLINDEX(1)%INDEXES(1,icell)
701 iy=grid%CELLINDEX(1)%INDEXES(2,icell)
702 IF(ix.GE.nxiso30(1,iso).AND.ix.LE.nxiso30(2,iso)+1.AND.
703 f iy.GE.nyiso30(1,iso).AND.iy.LE.nyiso30(2,iso)+1)
THEN
711 WRITE(gridman_unit,*)
" NXISO ",nxiso(iso)
712 WRITE(gridman_unit,*)
" NYISO ",nyiso(iso)
714 DO icell=1,grid%NCELLS
715 ix=grid%CELLINDEX(1)%INDEXES(1,icell)
716 iy=grid%CELLINDEX(1)%INDEXES(2,icell)
717 IF(ix.EQ.nxiso(iso).OR.ix.EQ.nxiso(iso)+1)
THEN
725 IF(ierr.NE.0)
GOTO 50
730 END SUBROUTINE eliminate_isolated_cells
733 SUBROUTINE assign_surface_markers(IERR)
734 INTEGER(GRIDMAN_SP) :: ICELL1,ICELL2,IEDGE,IE,N,IX,IY,
736 LOGICAL :: LPOL(grid%nedges)
737 INTEGER,
INTENT(OUT) :: IERR
743 DO iedge=1,grid%NEDGES
744 icell1=grid%CELLS(1,iedge)
745 icell2=grid%CELLS(2,iedge)
746 IF(icell1.LT.1.AND.icell2.LT.1) cycle
747 IF(icell1.LT.1.OR.icell2.LT.1) n=n+1
753 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
754 w
"cannot allocate index for surface markers"
761 DO ie=1,grid%EDGEINDEX(2)%NELEMENTS
762 iedge=grid%EDGEINDEX(2)%INDEXES(0,ie)
764 ixy(iedge)=grid%EDGEINDEX(2)%INDEXES(2,ie)
767 DO ie=1,grid%EDGEINDEX(3)%NELEMENTS
768 iedge=grid%EDGEINDEX(3)%INDEXES(0,ie)
770 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
772 WRITE(gridman_unit,*)
"Same edge is both poloidal and radial"
773 WRITE(gridman_unit,*)
" IEDGE, IY ",iedge,ixy(iedge)
777 ixy(iedge)=grid%EDGEINDEX(3)%INDEXES(1,ie)
782 DO iedge=1,grid%NEDGES
783 icell1=grid%CELLS(1,iedge)
784 icell2=grid%CELLS(2,iedge)
785 IF(icell1.LT.1.OR.icell2.LT.1)
THEN
788 ix=grid%CELLINDEX(1)%INDEXES(1,icell1)
789 iy=grid%CELLINDEX(1)%INDEXES(2,icell1)
791 IF(icell2.LT.1) cycle
792 ix=grid%CELLINDEX(1)%INDEXES(1,icell2)
793 iy=grid%CELLINDEX(1)%INDEXES(2,icell2)
797 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
799 WRITE(gridman_unit,*)
800 w
"Index is out of range in ASSIGN_SURFACE_MARKERS"
801 WRITE(gridman_unit,*)
" IE, N ",ie,n
805 grid%EDGEINDEX(1)%INDEXES(0,ie)=iedge
808 IF(ixy(iedge).LT.iy)
THEN
810 grid%EDGEINDEX(1)%INDEXES(1,ie)=-1
813 grid%EDGEINDEX(1)%INDEXES(1,ie)=-4
817 IF(ixy(iedge).LT.ix)
THEN
819 grid%EDGEINDEX(1)%INDEXES(1,ie)=-2
822 grid%EDGEINDEX(1)%INDEXES(1,ie)=-3
829 WRITE(gridman_unit,*)
"ERROR in GRIDMAN_CARRE2GRID: ",
831 WRITE(gridman_unit,*)
"Mismatch in ASSIGN_SURFACE_MARKERS"
832 WRITE(gridman_unit,*)
" IE, N ",ie,n
838 END SUBROUTINE assign_surface_markers
854 u gridman_unit,gridman_dbg,gridman_length
856 u gridman_carre2grid_fort30,
862 CHARACTER(*),
INTENT(IN) :: FNAME
864 INTEGER,
INTENT(OUT) :: IERR
870 LOGICAL,
OPTIONAL :: LEIR
872 CHARACTER(GRIDMAN_LENGTH) :: SONNETFILE
873 INTEGER(GRIDMAN_SP) :: NX,NY,NNCUT,NNISO
875 INTEGER(GRIDMAN_SP),
ALLOCATABLE :: NXCUT(:,:),NYCUT(:,:),
876 i nxiso(:,:),nyiso(:,:)
877 REAL(GRIDMAN_DP),
ALLOCATABLE :: BR(:,:,:),BZ(:,:,:)
880 w
WRITE(gridman_unit,*)
"Starting GRIDMAN_CARRE_READ30_GRID"
886 s nniso,nxiso,nyiso,br,bz,ierr)
888 WRITE(gridman_unit,*)
"GRIDMAN_CARRE_READ30_GRID terminated"
892 CALL gridman_carre2grid_fort30(grid,1_gridman_sp,1_gridman_sp,
893 s nx,ny,nncut,nxcut,nycut,
894 s nniso,nxiso,nyiso,br,bz,
895 s 1_gridman_sp,1_gridman_sp,
898 IF(
ALLOCATED(nxcut))
DEALLOCATE(nxcut)
899 IF(
ALLOCATED(nycut))
DEALLOCATE(nycut)
900 IF(
ALLOCATED(nxiso))
DEALLOCATE(nxiso)
901 IF(
ALLOCATED(nyiso))
DEALLOCATE(nyiso)
902 IF(
ALLOCATED(br))
DEALLOCATE(br)
903 IF(
ALLOCATED(bz))
DEALLOCATE(bz)
907 WRITE(gridman_unit,*)
"GRIDMAN_CARRE_READ30_GRID terminated"
911 grid%DESCRIPTION=sonnetfile
914 w
WRITE(gridman_unit,*)
"GRIDMAN_CARRE_READ30_GRID finished"
928 u gridman_unit,gridman_dbg
935 CHARACTER(*),
INTENT(IN) :: FNAME
937 INTEGER,
INTENT(OUT) :: IERR
942 LOGICAL,
OPTIONAL :: LEIR
944 INTEGER(GRIDMAN_SP) :: NX,NY,NNCUT,NNISO
946 INTEGER(GRIDMAN_SP),
ALLOCATABLE :: NXCUT(:),NYCUT(:),
948 REAL(GRIDMAN_DP),
ALLOCATABLE :: BR(:,:,:),BZ(:,:,:),
950 REAL(GRIDMAN_DP) :: RBT
953 w
WRITE(gridman_unit,*)
"Starting GRIDMAN_CARRE_READSONNET_GRID"
960 s rbt,br,bz,pit,bc,ierr)
962 WRITE(gridman_unit,*)
"GRIDMAN_CARRE_READSONNET_GRID terminated"
968 s nxcut,nycut,nniso,nxiso,nyiso,
969 s br,bz,1_gridman_sp,1_gridman_sp,
972 IF(
ALLOCATED(nxcut))
DEALLOCATE(nxcut)
973 IF(
ALLOCATED(nycut))
DEALLOCATE(nycut)
974 IF(
ALLOCATED(nxiso))
DEALLOCATE(nxiso)
975 IF(
ALLOCATED(nyiso))
DEALLOCATE(nyiso)
976 IF(
ALLOCATED(br))
DEALLOCATE(br)
977 IF(
ALLOCATED(bz))
DEALLOCATE(bz)
978 IF(
ALLOCATED(bc))
DEALLOCATE(bc)
979 IF(
ALLOCATED(pit))
DEALLOCATE(pit)
983 WRITE(gridman_unit,*)
"GRIDMAN_CARRE_READSONNET_GRID terminated"
988 w
WRITE(gridman_unit,*)
"GRIDMAN_CARRE_READSONNET_GRID finished"
subroutine gridman_carre2grid(GRID, LXB, LYB, NXB, NYB, NNCUT, NXCUT, NYCUT, NNISO, NXISO, NYISO, BR, BZ, LX, LY, NXL, NYL, IERR, LEIR)
Convert B2 (CARRE, SONNET) grid into GRIDMAN_GRID grid object.
real(gridman_dp), save, public gridman_tol
Tolerance parameter which is used to compare two real numbers.
subroutine gridman_grid_eliminate_cells(GRID_NEW, GRID, LTAKE, IERR)
Eliminate cells from GRIDMAN_GRID object.
integer, parameter, public gridman_dp
Kind parameter for real numbers.
Explicit interfaces to GRIDMAN subroutines and functions.
subroutine gridman_grid_allocate(GRID, TYPE, NEDGES, NPOINTS, NCELLS, IERR, NEDGEINDEX, NCELLINDEX)
Allocate GRIDMAN_GRID object.
subroutine gridman_grid2d_check(GRID, RES, IERR)
Check correctness of the 2D grid object.
Data-type which describes a grid as a set of edges, methods in grid.f.
subroutine gridman_grid_deallocate(GRID, IERR)
Deallocate grid object.
subroutine gridman_index_allocate(INDEX, NINDEX, NELEMENTS, IERR)
Allocate index object.
subroutine gridman_grid_copy(GRID2, GRID1, IERR)
Create a copy of the grid object.
subroutine gridman_carre_readsonnet_grid(GRID, FNAME, IERR, LEIR)
Read CARRE grid in SONNET format, return GRID object.
Definition of data types, global constants and variables.
subroutine gridman_carre_read30_grid(GRID, FNAME, IERR, LEIR)
Read B2 (CARRE, SONNET) grid from fort.30, return GRID object.
subroutine gridman_grid_remove_free_edges(GRID_NEW, GRID, IERR)
Remove edges which do not belong to any cell from the GRIDMAN_GRID object.
integer, parameter, public gridman_sp
Kind parameter for integer numbers.