!------------------------------------------------------------------------------| !------------------------------------------------------------------------------| ! | ! ||===\\ | ! || \\ | ! || || //==\\ || || //==|| ||/==\\ | ! || || || || || || || || || || | ! || // || || || || || || || | ! ||===// \\==// \\==\\ \\==\\ || | ! | !------------------------------------------------------------------------------| !------------------------------------------------------------------------------| ! | ! DEFINE_BC Apr. 2007 | ! | !------------------------------------------------------------------------------| !------------------------------------------------------------------------------| subroutine define_bc (params,osolve,vo) !------------------------------------------------------------------------------| !(((((((((((((((( Purpose of the routine )))))))))))))))))))))))))))))))))))))) !------------------------------------------------------------------------------| ! subroutine to implement the boundary conditions. ! Here the user should define if the dof is fixed by setting ! kfix((inode-1)*3+idof) to 1 (node inode and dof idof) ! and setting the corresponding value of u, v, or w to the set fixed value ! Same operation for kfixt and temp but for a single dof ! vo is the structure that contains the void information !------------------------------------------------------------------------------| !(((((((((((((((( declaration of the subroutine arguments )))))))))))))))))))) !------------------------------------------------------------------------------| use definitions !use mpi implicit none include 'mpif.h' type (parameters) params type (octreesolve) osolve type (void) vo !------------------------------------------------------------------------------| !(((((((((((((((( declaration of the subroutine internal variables ))))))))))))) !------------------------------------------------------------------------------| integer i,iproc,nproc,ierr double precision eps,lsf0,pi,l,h,x0,x1,x2,phi integer ie,ij,j,jp character fname*256 !------------------------------------------------------------------------------| !------------------------------------------------------------------------------| call mpi_comm_size (mpi_comm_world,nproc,ierr) call mpi_comm_rank (mpi_comm_world,iproc,ierr) eps=1.d-10 osolve%kfix=0 osolve%kfixt=0 pi=atan(1.d0)*4.d0 l=0.1d0 h=0.1d0 !x0=0.5d0 phi=45.d0 phi=phi/180.d0*pi !x1=x0-l*(1.d0-cos(phi))/sin(phi) !x2=x0+l/tan(phi) !select case(trim(params%infile)) j = index(params%infile, '/', .true.) fname = params%infile(j+1:len(params%infile)) select case(trim(fname)) case('input.txt','input.small.txt') do i=1,osolve%nnode ! 75% obliquity ! x0=osolve%y(i)*2.d0-.5d0 ! 50% obliquity x0=osolve%y(i) x0=min(x0,0.75d0) x0=max(x0,0.25d0) if (osolve%x(i).lt.eps) then osolve%kfix((i-1)*3+1)=1 ; osolve%u(i)=1.d0 ! osolve%u(i)=1.d0 ! osolve%kfix((i-1)*3+2)=1 ; osolve%v(i)=0.d0 ! osolve%kfix((i-1)*3+3)=1 ; osolve%w(i)=0.d0 endif if (osolve%x(i).gt.1.d0-eps) then osolve%kfix((i-1)*3+1)=1 ; osolve%u(i)=0.d0 ! osolve%kfix((i-1)*3+2)=1 ; osolve%v(i)=0.d0 ! osolve%kfix((i-1)*3+3)=1 ; osolve%w(i)=0.d0 endif if (osolve%y(i).lt.eps) then ! osolve%kfix((i-1)*3+1)=1 ; osolve%u(i)=0.d0 osolve%kfix((i-1)*3+2)=1 ; osolve%v(i)=0.d0 ! osolve%kfix((i-1)*3+3)=1 ; osolve%w(i)=0.d0 endif if (osolve%y(i).gt.1.d0-eps) then ! osolve%kfix((i-1)*3+1)=1 ; osolve%u(i)=0.d0 osolve%kfix((i-1)*3+2)=1 ; osolve%v(i)=0.d0 ! osolve%kfix((i-1)*3+3)=1 ; osolve%w(i)=0.d0 endif if (osolve%z(i).lt.eps) then osolve%kfix((i-1)*3+1)=1 ; osolve%u(i)=0.d0 osolve%kfix((i-1)*3+2)=1 ; osolve%v(i)=0.d0 osolve%kfix((i-1)*3+3)=1 ; osolve%w(i)=0.d0 if (osolve%x(i).le.x0) then osolve%u(i)=1.d0 endif osolve%kfixt(i)=1 osolve%temp(i)=1.d0 endif if (osolve%z(i).gt.1.d0-eps) then osolve%kfix((i-1)*3+1)=1 ; osolve%u(i)=0.d0 osolve%kfix((i-1)*3+2)=1 ; osolve%v(i)=0.d0 osolve%kfix((i-1)*3+3)=1 ; osolve%w(i)=0.d0 osolve%kfixt(i)=1 osolve%temp(i)=0.d0 endif if (.not.vo%influid(i)) then osolve%kfixt(i)=1 osolve%temp(i)=0.d0 endif enddo case ('input.jgr') call define_bc_jgr (osolve%nnode,osolve%kfix,osolve%kfixt,osolve%x,osolve%y,osolve%z,osolve%u,osolve%v,osolve%w,osolve%temp,vo) case ('input.sphere') call define_bc_sphere(osolve%nnode,osolve%kfix,osolve%kfixt,osolve%x,osolve%y,osolve%z,osolve%u,osolve%v,osolve%w,osolve%temp,vo) case ('input.3Dpunch') call define_bc_3Dpunch(osolve%nnode,osolve%kfix,osolve%kfixt,osolve%x,osolve%y,osolve%z,osolve%u,osolve%v,osolve%w,osolve%temp,vo) case ('input.2Dpunch') call define_bc_2Dpunch(osolve%nnode,osolve%kfix,osolve%kfixt,osolve%x,osolve%y,osolve%z,osolve%u,osolve%v,osolve%w,osolve%temp,vo) case ('input.2Dpunch_vert') call define_bc_2Dpunch_vert(osolve%nnode,osolve%kfix,osolve%kfixt,osolve%x,osolve%y,osolve%z,osolve%u,osolve%v,osolve%w,& osolve%temp,vo) case ('input.folding') call define_bc_folding(osolve%nnode,osolve%kfix,osolve%kfixt,osolve%x,osolve%y,osolve%z,osolve%u,osolve%v,osolve%w,osolve%temp,vo) case ('input.pipo') call define_bc_pipo (osolve%nnode,osolve%kfix,osolve%kfixt,osolve%x,osolve%y,osolve%z,osolve%u,osolve%v,osolve%w,osolve%temp,vo) case ('input.ritske') call define_bc_ritske(osolve%nnode,osolve%kfix,osolve%kfixt,osolve%x,osolve%y,osolve%z,osolve%u,osolve%v,osolve%w,osolve%temp,& vo) case ('input.ritske_isurf') call define_bc_ritske_isurf (osolve%nnode,osolve%kfix,osolve%kfixt,osolve%x,osolve%y,osolve%z,osolve%u,osolve%v,osolve%w,& osolve%temp,vo) case ('input.subduction') call define_bc_subduction (osolve%nnode,osolve%kfix,osolve%kfixt,osolve%x,osolve%y,osolve%z,osolve%u,osolve%v,osolve%w,& osolve%temp,vo) case ('input.riedel') call define_bc_riedel(osolve%nnode,osolve%kfix,osolve%kfixt,osolve%x,osolve%y,osolve%z,osolve%u,osolve%v,osolve%w,osolve%temp,vo) case ('input.parallipipede') call define_bc_parallipipede (osolve%nnode,osolve%kfix,osolve%kfixt,osolve%x,osolve%y,osolve%z,osolve%u,osolve%v,osolve%w,& osolve%temp,vo) case default if (iproc.eq.0) print *,params%infile call stop_run (' pb with input file in define_bc.f90') end select ! here we need to impose that the bc satisfy the bad faces constrains do ie=1,osolve%nface do j=1,4 jp=1+mod(j,4) i=osolve%iface(j+4,ie) if (osolve%kfix((i-1)*3+1).eq.1) osolve%u(i)=(osolve%u(osolve%iface(j,ie))+osolve%u(osolve%iface(jp,ie)))/2.d0 if (osolve%kfix((i-1)*3+2).eq.1) osolve%v(i)=(osolve%v(osolve%iface(j,ie))+osolve%v(osolve%iface(jp,ie)))/2.d0 if (osolve%kfix((i-1)*3+3).eq.1) osolve%w(i)=(osolve%w(osolve%iface(j,ie))+osolve%w(osolve%iface(jp,ie)))/2.d0 if (osolve%kfixt(i).eq.1) osolve%temp(i)=(osolve%temp(osolve%iface(j,ie))+osolve%temp(osolve%iface(jp,ie)))/2.d0 enddo i=osolve%iface(9,ie) if (osolve%kfix((i-1)*3+1).eq.1) osolve%u(i)=sum(osolve%u(osolve%iface(1:4,ie)))/4.d0 if (osolve%kfix((i-1)*3+2).eq.1) osolve%v(i)=sum(osolve%v(osolve%iface(1:4,ie)))/4.d0 if (osolve%kfix((i-1)*3+3).eq.1) osolve%w(i)=sum(osolve%w(osolve%iface(1:4,ie)))/4.d0 if (osolve%kfixt(i).eq.1) osolve%temp(i)=sum(osolve%temp(osolve%iface(1:4,ie)))/4.d0 enddo if (params%debug==2) call output_bc (osolve) return end !------------------------------------------------------------------------------| !------------------------------------------------------------------------------|