! Copyright (C) 2011 UNESCO-IHE, WL|Delft Hydraulics and Delft University ! ! Dano Roelvink, Ap van Dongeren, Ad Reniers, Jamie Lescinski, ! ! Jaap van Thiel de Vries, Robert McCall ! ! ! ! d.roelvink@unesco-ihe.org ! ! UNESCO-IHE Institute for Water Education ! ! P.O. Box 3015 ! ! 2601 DA Delft ! ! The Netherlands ! ! ! ! This library is free software; you can redistribute it and/or ! ! modify it under the terms of the GNU Lesser General Public ! ! License as published by the Free Software Foundation; either ! ! version 2.1 of the License, or (at your option) any later version. ! ! ! ! This library 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 ! ! Lesser General Public License for more details. ! ! ! ! You should have received a copy of the GNU Lesser General Public ! ! License along with this library; if not, write to the Free Software ! ! Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 ! ! USA ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! module landslide_module implicit none type landslides ! landslide file names character*256 :: lsinpfile ! landslide time stamps real*8 :: lsinpt ! timestep of the landslide files real*8 :: lsdt end type landslides contains subroutine readlsfile(s,par) use params use xmpi_module use spaceparams use readkey_module use filefunctions use interp use logging_module, only: report_file_read_error IMPLICIT NONE type(parameters) :: par type(spacepars) :: s type(landslides), dimension(:), pointer, save :: ls integer :: i,j,fid,ier,it,nls ! z coordinates real*8, dimension(:,:), pointer :: dzbls ! counter of the used landslide file integer, save :: ls_ind character(1) :: ch allocate(ls(1:par%nslide)) allocate(dzbls(1:par%nx+1,1:par%ny+1)) s%dzblsdt = 0 fid=create_new_fid() open(fid,file=par%slidefile) ier=0 ! read in times and landslide file names do i=1,par%nslide read(fid,*,iostat=ier) ls(i)%lsinpt, ls(i)%lsinpfile if (ier .ne. 0) then call report_file_read_error(par%slidefile) endif enddo close(fid) ! only update if there are still landslide files to be ! read in, otherwise s%dzblsdt remains zero if (par%t<=ls(par%nslide)%lsinpt) then ! find the landslide file for the actual hydrodynamic time ! and compute lsdt ls_ind=0 do i=1,par%nslide-1 if (ls(i)%lsinpt<=par%t) then ls_ind=ls_ind+1 endif end do ! add one afterwards because we want to update ! towards the next timestep ls_ind=ls_ind+1 if (ls_ind==1) then ! The first time stamp equals the first ! time step/intervall ls(ls_ind)%lsdt=ls(ls_ind)%lsinpt else ls(ls_ind)%lsdt=ls(ls_ind)%lsinpt-ls(ls_ind-1)%lsinpt endif ! read in landslide file with the index ls_ind ! that corresponds to the actual hydrodynamic time fid=create_new_fid() open (fid,file=ls(ls_ind)%lsinpfile) do j=1,par%ny+1 read(fid,*,iostat=ier)(dzbls(i,j),i=1,par%nx+1) if (ier .ne. 0) then call report_file_read_error(ls(ls_ind)%lsinpfile) endif end do close(fid) ! compute rate of bed change per second !(just in case time step between input files is not one second) s%dzblsdt=1/ls(ls_ind)%lsdt*dzbls endif deallocate(ls) deallocate(dzbls) end subroutine readlsfile end module landslide_module