Skip to content
Snippets Groups Projects
read_reclist.f90 2.12 KiB
!---------------------------------------------------------------------------------------
! PREP_SYNDATA: read_reclist
!---------------------------------------------------------------------------------------
!  FLEXINVERT is free software: you can redistribute it and/or modify
!  it under the terms of the GNU General Public License as published by
!  the Free Software Foundation, either version 3 of the License, or
!  (at your option) any later version.
!
!  FLEXINVERT is distributed in the hope that it will be useful,
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
!  GNU General Public License for more details.
!
!  You should have received a copy of the GNU General Public License
!  along with FLEXINVERT.  If not, see <http://www.gnu.org/licenses/>.
!
!  Copyright 2017, Rona Thompson
!---------------------------------------------------------------------------------------
!
!> read_reclist
!!
!! Purpose:    Reads the receptor list file and counts the number of receptors.
!!
!---------------------------------------------------------------------------------------

subroutine read_reclist(filename)

  use mod_var

  implicit none

  character(len=max_path_len), intent(in) :: filename
  character(len=200)                      :: line
  integer                                 :: ierr
  integer                                 :: cnt

  ! count number of receptors

  open(100,file=trim(filename),action='read',status='old',iostat=ierr)
  if(ierr.gt.0) then
    write(logid,*) 'ERROR: cannot open: '//trim(filename)
    stop
  endif
  write(logid,*) 'Reading receptors file: '//trim(filename)

  cnt = 0
  do while (ierr.eq.0)
    read(100,*,iostat=ierr,end=10) line
    cnt = cnt + 1
  end do
10 continue
  close(100)

  nrec = cnt
  write(logid,*) 'Number of receptors: ',nrec

  ! read receptors

  allocate ( recname(nrec) )

  open(100,file=trim(filename),action='read',status='old',iostat=ierr)
  write(logid,*) 'Receptors: '

  do cnt = 1, nrec
    read(100,*) recname(cnt)
    write(logid,*) recname(cnt)
  end do

  close(100)
end subroutine read_reclist