! Simple prep script for METIS ! Inputs: hgrid.gr3 (with b.c.); vgrid.in ! Outputs: graphinfo (required by METIS) ! ifort -mcmodel=medium -O2 -CB -g -traceback -o metis_prep metis_prep.f90 ! METIS usage: ! ./gpmetis graphinfo -ufactor=1.01 -seed=15 (nproc is # of compute cores excluding scribes) ! Afterward, use awk to generate partition.prop: ! awk '{print NR,$0}' graphinfo.part.88 > partition.prop (using nproc=88 cores as e.g.) program metis_prep implicit none ! include 'metis.h' integer,parameter :: rkind = 8 logical :: found integer :: i,j,k,l,ie,je,ne,np,ip,ip0,mnei,n1,n2,nope,neta,mnond,nt,stat,nn,icount,ii, & &new,ivcor,nvrt,kz,nsig,kin,mxnedge,nedge,ntedge,wgtflag,numflag,ncon,ndims,kbetmp, & &nproc,nxq(3,4,4),nland,mnlnd,nvel,objval ! integer :: options(METIS_NOPTIONS) real(rkind) :: h_c,h_s,theta_f,theta_b,dtmp,etmp,ptmp,stmp integer, allocatable :: i34(:),elnode(:,:),nne(:),indel(:,:),ic3(:,:), & &isbnd(:),nond(:),iond(:,:),kbp(:),adjncy(:),xadj(:),nlev(:),vwgt(:),adjwgt(:), & &vtxdist(:),nlnd(:),ilnd(:,:),part(:) real(rkind), allocatable :: ztot(:),sigma(:),dp(:) real(4),allocatable :: tpwgts(:),ubvec(:) ! print*, 'Input # of MPI processes (compute):' ! read*, nproc do k=3,4 !elem. type do i=1,k !local index do j=1,k-1 !offset nxq(j,i,k)=i+j if(nxq(j,i,k)>k) nxq(j,i,k)=nxq(j,i,k)-k if(nxq(j,i,k)<1.or.nxq(j,i,k)>k) then write(*,*)'INIT: nx wrong',i,j,k,nxq(j,i,k) stop endif enddo !j enddo !i enddo !k !----------------------------------------------------------------------------- ! Aquire and construct global data tables !----------------------------------------------------------------------------- ! Aquire global grid size open(14,file='hgrid.gr3',status='old') read(14,*); read(14,*) ne,np ! Aquire global element-node tables from hgrid.gr3 allocate(i34(ne),elnode(4,ne),dp(np),kbp(np),stat=stat) do i=1,np read(14,*)j,dtmp,dtmp,dp(i) enddo; do i=1,ne read(14,*) ie,i34(ie),(elnode(k,ie),k=1,i34(ie)) if(i34(ie)/=3.and.i34(ie)/=4) then write(*,*) 'AQUIRE_HGRID: Unknown type of element',ie,i34(ie) stop endif enddo !i ! Count number of elements connected to each node (global) allocate(nne(np),stat=stat) nne=0 do ie=1,ne do k=1,i34(ie) ip=elnode(k,ie) nne(ip)=nne(ip)+1 enddo !k enddo !ie ! Check hanging nodes found=.false. do ip=1,np if(nne(ip)==0) then found=.true. write(*,*) 'Hanging node:',ip endif enddo if(found) then write(*,*)'check hanging nodes' stop endif ! Maximum number of elements connected to a node mnei=0 do ip=1,np mnei=max(mnei,nne(ip)) enddo ! Build global node-element and self-reference table table allocate(indel(mnei,np),stat=stat) nne=0 do ie=1,ne do k=1,i34(ie) ip=elnode(k,ie) nne(ip)=nne(ip)+1 indel(nne(ip),ip)=ie enddo !k enddo !ie !Compute mnei_p (max. # of nodes around a node) ! mnei_p=0 ! do i=1,np ! icount=0 ! do j=1,nne(i) ! icount=icount+i34(ie)-2 !# of new surrounding nodes ! enddo !j ! mnei_p=max(mnei_p,icount+1) !account for bnd ball ! enddo !i ! if(myrank==0.and..not.full_aquire) write(16,*)'mnei, mnei_p = ',mnei,mnei_p ! Build global element-side-element table; this won't be affected by re-arrangement below allocate(ic3(4,ne),stat=stat) do ie=1,ne do k=1,i34(ie) ic3(k,ie)=0 !index for boundary sides n1=elnode(nxq(1,k,i34(ie)),ie) n2=elnode(nxq(2,k,i34(ie)),ie) do l=1,nne(n1) je=indel(l,n1) if(je/=ie.and.(elnode(1,je)==n2.or.elnode(2,je)==n2.or. & &elnode(3,je)==n2.or.(i34(je)==4.and.elnode(4,je)==n2))) ic3(k,ie)=je enddo !l je=ic3(k,ie) if(je/=0) then do l=1,i34(je) if(elnode(nxq(1,l,i34(je)),je)==n1.and.elnode(nxq(2,l,i34(je)),je)==n2) then write(*,*) 'Elem ', ie, ' and ', je, ' have opposite orientation' stop endif end do !l endif enddo !k enddo !ie !new39 ! ip0=718 ! do i=1,nne(ip0) ! ie=indel(i,ip0) ! write(99,*)'Init ball:',nne(ip0),ie ! write(99,*)'ic3:',ic3(1:i34(ie),ie) ! enddo !i ! ine to be re-arranged in counter-clockwise fashion after boundary info is read in ! Count global number of sides and build global element-side index table ! if(allocated(js)) deallocate(js); allocate(js(4,ne),stat=stat); ! if(stat/=0) call parallel_abort('AQUIRE_HGRID: js allocation failure') ! ns=0 ! do ie=1,ne ! do j=1,i34(ie) !visit each side associated with element ie ! if(ic3(j,ie)==0.or.ie=1 if(nvrt<2) stop 'nvrt<2' if(kz<1) then !.or.kz>nvrt-2) then write(*,*)'Wrong kz:',kz stop endif if(h_s<6.d0) then write(*,*)'h_s needs to be larger:',h_s stop endif ! Allocate vertical layers arrays allocate(ztot(nvrt),sigma(nvrt),stat=stat) nsig=nvrt-kz+1 !# of S levels (including "bottom" & f.s.) ! # of z-levels excluding "bottom" at h_s read(19,*) !for adding comment "Z levels" do k=1,kz-1 read(19,*)j,ztot(k) if(ztot(k)>=-h_s) then write(*,*)'Illegal Z level:',k stop endif if(k>1) then; if(ztot(k)<=ztot(k-1)) then write(*,*)'z-level inverted:',k stop endif; endif enddo !k read(19,*) !level kz ! In case kz=1, there is only 1 ztot(1)=-h_s ztot(kz)=-h_s read(19,*) !for adding comment "S levels" read(19,*)h_c,theta_b,theta_f if(h_c<5._rkind.or.h_c>=h_s) then !large h_c to avoid 2nd type abnormaty write(*,*)'h_c needs to be larger:',h_c stop endif if(theta_b<0._rkind.or.theta_b>1._rkind) then write(*,*)'Wrong theta_b:',theta_b stop endif if(theta_f<=0._rkind) then write(*,*)'Wrong theta_f:',theta_f stop endif sigma(1)=-1._rkind !bottom sigma(nsig)=0._rkind !surface read(19,*) !level kz do k=kz+1,nvrt-1 kin=k-kz+1 read(19,*) j,sigma(kin) if(sigma(kin)<=sigma(kin-1).or.sigma(kin)>=0._rkind) then write(*,*)'Check sigma levels at:',k,sigma(kin),sigma(kin-1) stop endif enddo !k read(19,*) !level nvrt close(19) else if(ivcor==1) then !localized sigma read(19,*)nvrt read(19,*)kbp(1:np) close(19) allocate(ztot(nvrt),sigma(nvrt),stat=stat) !for output only - remove later ztot=0._rkind; sigma=0._rkind kz=1; h_s=0._rkind; h_c=0._rkind; theta_b=0._rkind; theta_f=0._rkind else stop 'GRID_SUBS: Unknown ivcor' endif !ivcor ! Count number of edges in dual graph (element as 'vertex') allocate(adjncy(1000),stat=stat) !for single element ntedge=0 !total # of edges in the grid mxnedge=0 !max. # of local edges do ie=1,ne nedge=0 !# of local edges adjncy=0 !list of global element indices do j=1,i34(ie) ip=elnode(j,ie) do k=1,nne(ip) je=indel(k,ip) if(je/=ie) then found=.false. do l=1,nedge if(adjncy(l)==je) then found=.true. exit endif enddo if(.not.found) then !new edge nedge=nedge+1 if(nedge>1000) stop 'PARTITION: bound (1)' adjncy(nedge)=je endif endif enddo !k enddo !j ntedge=ntedge+nedge mxnedge=max(mxnedge,nedge) enddo !ie deallocate(adjncy) ! Use vertex (elem) and/or edge weights wgtflag = 3 ! 0: none; 1: edges; 2: vertices; 3: vertices & edges ! Number of weights associated with each vertex, used to optimize the ! partition ncon = 4 ! Allocate storage for dual graph if(allocated(xadj)) deallocate(xadj); allocate(xadj(ne+1),stat=stat); if(allocated(adjncy)) deallocate(adjncy); allocate(adjncy(ntedge),stat=stat) ! if(allocated(xyz)) deallocate(xyz); allocate(xyz(2*ne),stat=stat) if(allocated(nlev)) deallocate(nlev); allocate(nlev(ne),stat=stat) !estimate of number of active levels if(wgtflag==2.or.wgtflag==3) then if(allocated(vwgt)) deallocate(vwgt); allocate(vwgt(ne*ncon),stat=stat) endif if(wgtflag==1.or.wgtflag==3) then if(allocated(adjwgt)) deallocate(adjwgt); allocate(adjwgt(ntedge),stat=stat) endif ! Assign vertex coordinates & weights ! Weights based on estimated number of active levels do ie=1,ne ! xtmp=0._rkind !xctr ! ytmp=0._rkind dtmp=real(5.d10,rkind) !min. depth do j=1,i34(ie) ip=elnode(j,ie) ! xtmp=xtmp+real(xproj(ip),rkind)/real(i34(ie),rkind) ! ytmp=ytmp+real(yproj(ip),rkind)/real(i34(ie),rkind) if(dp(ip)h_s kbetmp=0 !element bottom index; also works for 2D model do j=1,kz-1 if(-dtmp>=ztot(j).and.-dtmp