!####################################################################### ! SUBROUTINE --- sub_read_initial_data --- ### !####################################################################### ! ### ! Subroutine for Input of the Initial Data of SPH particles ### ! and Allocate of Variables ### ! ### ! Variables for Input Data ### ! np ! Total Number of SPH Particles ### ! time_sta ! Starting Time ### ! imat(i) ! Material ID ### ! m(i) ! Mass ### ! x(3,i) ! Position (x,y,z) ### ! v(3,i) ! Velocity (x,y,z) ### ! h(i) ! Smoothing Length ### ! e(i) ! Specific Internal Energy ### ! ### ! 2009/07/24 ### ! 2009/08/27 ### ! 2011/06/23 ### ! 2011/09/13 ### !####################################################################### subroutine sub_read_initial_data use mod_parameter use mod_variable implicit none !==== Variables Used in This Subroutine ================================ integer(4) :: i ! Particle Number integer(4) :: i_tmp ! Dummy Variable for Particle Number real(8) :: d_tmp ! Dummy Variable for Density real(8) :: p_tmp ! Dummy Variable for Pressure character(3) :: tmp3 ! Dummy Variable for Status integer(4) :: as_nbl ! Array Size of Neighbor List integer(4) :: as_nbg ! Array Size of Neighbor List for Gravity integer(4) :: as_node ! Array Size of Node !----------------------------------------------------------------------- !======================================================================= !==== Programs ========================================================= !======================================================================= !---- Open Initial Data File ---- open(50,file=FILE_INITIAL) !---- Read Status ---- read(50,'(a3)') tmp3 !---- Read Initial Time ---- read(50,'(e15.7)') time_sta !---- Read Particle Number ---- read(50,'(i9)') np !---- Calculate Array Size of Neighbor List ---- as_nbl = int(FCTR_NB*dble(np)) as_nbg = int(FCTR_NBG*dble(np)) as_node = int(FCTR_NODE*dble(np)) !---- Allocate Array ---- allocate(imat(np)) allocate(m(np)) allocate(x(3,np)) allocate(v(3,np)) allocate(h(np)) allocate(d(np)) allocate(p(np)) allocate(e(np)) allocate(sv(np)) allocate(a(3,np)) allocate(a_grav(3,np)) allocate(dedt(np)) allocate(a1(3,np)) allocate(dedt1(np)) allocate(nu_max(np)) allocate(omega(np)) allocate(zeta(np)) allocate(nb(np)) allocate(flag_node(as_node)) allocate(center_node(3,as_node)) allocate(center_mass_node(3,as_node)) allocate(mass_node(as_node)) allocate(h_max_node(as_node)) allocate(leng_node(as_node)) allocate(radius_node(as_node)) allocate(head_branch_id(as_node)) allocate(num_branch(as_node)) allocate(nbi_list(as_nbl,0:N_TRD-1)) allocate(dis2_nbi_list(as_nbl,0:N_TRD-1)) allocate(wait_list(as_node,0:N_TRD-1)) allocate(head_ptcl_id_list(as_node)) allocate(ptcl_id_list(np)) allocate(np_node(as_node)) allocate(ptcl_id_list_branch(np)) allocate(pdd(np)) allocate(id_nb(as_nbg,0:N_TRD-1)) allocate(mc_nb(as_nbg,0:N_TRD-1)) allocate(xc_nb(3,as_nbg,0:N_TRD-1)) allocate(dis2_nb(as_nbg,0:N_TRD-1)) allocate(t(np),t_pk(np),p_pk(np),iec(np),it(np)) t=0.0e0_8 t_pk=0.0e0_8 p_pk=0.0e0_8 iec=0 it=0 !--- temptemp ---- !allocate(ec_tmp(np),tt(np),tt_pk(np)) !ec_tmp=0.0e0_8 !tt=0.0e0_8 !tt_pk=0.0e0_8 !----------------- if (FLAG_5PHASE_EOS == 1) then allocate(s(np)) do i=1,np s(i)=0.0e0_8 enddo endif !---- Read Initial Particle Data ------------------------------------- do i=1,np read(50,'(i9,i2,11e15.7)') & & i_tmp,imat(i),m(i),x(1,i),x(2,i),x(3,i), & & v(1,i),v(2,i),v(3,i), & & h(i),d_tmp,p_tmp,e(i) end do !---- Close File ---- close(50) return end subroutine sub_read_initial_data