module readsediment_module ! ! Conceptual possibilities: ! - like waterlevels and interpolating linearly, but what about point sources? ! - constant on the boundaries, but what about cross-shore gradients? ! implicit none save contains subroutine initsediment(s,par) ! nog aansluiten in initialize use params use spaceparams use paramsconst use filefunctions use logging_module implicit none type(spacepars), target :: s type(parameters), intent(in) :: par logical :: exists integer :: i,j,ff,fid,fid2,ier character(slen) :: testline exists = .false. ! if there is a file with initial ccg list, then use that inquire(file=par%ccginitfile,exist=exists) ! list of filenames with initial fields if (exists) then fid = create_new_fid() open(fid,file=par%ccginitfile) read(fid,*)testline if (trim(testline)=='INIFRACLIST') then ! we assume the order of the file follows the order of the fractions in the params.txt file do ff = 1, par%ngd read(fid,*)testline ! read next initial field file inquire(file=trim(testline),exist=exists) if (exists) then fid2 = create_new_fid() ! read per fraction do j=1,s%ny+1 read(fid2,*,iostat=ier)(s%ccg(i,j,ff),i=1,s%nx+1) if (ier .ne. 0) then call report_file_read_error(testline) endif enddo else call writelog('lwse','','Error: Initial sediment concentration file '//trim(testline)//' does not exist.') call halt_program() endif end do else call writelog('lwse','','Error: List of initial concentration field files should start with INIFRACLIST, ') call writelog('lwse','',' followed by no_of_fractions filenames containing the concentration fields.') call halt_program() end if close(fid) else ! no initial ccg0 file exists, ccg is assumed to be allocated and filled with zeros do ff = 1, par%ngd do i = 1, s%nx+1 do j = 1, s%ny+1 s%ccg(i,j,ff) = par%ccg0(ff) enddo enddo enddo endif end subroutine initsediment end module readsediment_module