aqu2d_read.f90 Source File


This file depends on

sourcefile~~aqu2d_read.f90~~EfferentGraph sourcefile~aqu2d_read.f90 aqu2d_read.f90 sourcefile~hydrograph_module.f90 hydrograph_module.f90 sourcefile~aqu2d_read.f90->sourcefile~hydrograph_module.f90 sourcefile~input_file_module.f90 input_file_module.f90 sourcefile~aqu2d_read.f90->sourcefile~input_file_module.f90 sourcefile~maximum_data_module.f90 maximum_data_module.f90 sourcefile~aqu2d_read.f90->sourcefile~maximum_data_module.f90 sourcefile~basin_module.f90 basin_module.f90 sourcefile~hydrograph_module.f90->sourcefile~basin_module.f90 sourcefile~time_module.f90 time_module.f90 sourcefile~hydrograph_module.f90->sourcefile~time_module.f90

Source Code

      subroutine aqu2d_read
    
      use hydrograph_module
      use input_file_module
      use maximum_data_module
      
      implicit none
      
      character (len=80) :: titldum = ""!           |title of file
      character (len=80) :: header = "" !           |header of file
      character (len=16) :: namedum = ""!           |
      integer :: eof = 0              !           |end of file
      integer :: imax = 0             !none       |determine max number for array (imax) and total number in file
      integer :: nspu = 0             !           |
      logical :: i_exist              !none       |check to determine if file exists
      integer :: i = 0                !none       |counter
      integer :: isp = 0              !none       |counter
      integer :: numb = 0             !           |
      integer :: iaq = 0              !none       |counter
      integer :: iaq_db = 0           !none       |counter
      integer :: ielem1 = 0           !none       |counter

      eof = 0
      imax = 0
      
    !!read data for aquifer elements for 2-D groundwater model
      inquire (file=in_link%aqu_cha, exist=i_exist)
      if (.not. i_exist .or. in_link%aqu_cha == "null" ) then
        allocate (aq_ch(0:0))
      else 
      do
        if (eof < 0) exit
        open (107,file=in_link%aqu_cha)
        read (107,*,iostat=eof) titldum
        if (eof < 0) exit
        read (107,*,iostat=eof) header
        if (eof < 0) exit
        imax = 0
        do while (eof == 0)
          read (107,*,iostat=eof) i
          if (eof < 0) exit
          imax = Max(imax,i)
        end do
      end do

      db_mx%aqu2d = imax
      allocate (aq_ch(sp_ob%aqu))
      rewind (107)
      read (107,*) titldum
      read (107,*) header

      do iaq_db = 1, imax

        read (107,*,iostat=eof) iaq, namedum, nspu
        if (eof < 0) exit
        
        if (nspu > 0) then
          backspace (107)
          allocate (elem_cnt(nspu), source = 0)
          read (107,*,iostat=eof) numb, aq_ch(iaq)%name, nspu, (elem_cnt(isp), isp = 1, nspu)
          if (eof < 0) exit
          
          call define_unit_elements (nspu, ielem1)
          
          allocate (aq_ch(iaq)%num(ielem1), source = 0)
          aq_ch(iaq)%num = defunit_num
          aq_ch(iaq)%num_tot = ielem1
          deallocate (defunit_num)

        end if
      end do
      end if

      close (107)
      
      return
      end subroutine aqu2d_read