source: flexpart.git/src/writeprecip.f90

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file was 92fab65, checked in by Ignacio Pisso <ip@…>, 4 years ago

add SPDX-License-Identifier to all .f90 files

  • Property mode set to 100644
File size: 2.2 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine writeprecip(itime,imem)
5
6  !*****************************************************************************
7  !                                                                            *
8  !  This routine produces a file containing total precipitation for each      *
9  !  releases point.                                                           *
10  !                                                                            *
11  !     Author: S. Eckhardt                                                    *
12  !     7 Mai 2017                                                             *
13  !*****************************************************************************
14
15  use point_mod
16  use par_mod
17  use com_mod
18
19  implicit none
20
21  integer :: jjjjmmdd,ihmmss,itime,i
22  real(kind=dp) :: jul
23  character :: adate*8,atime*6
24
25  integer :: ix,jy,imem
26  real :: xp1,yp1
27
28 
29  if (itime.eq.0) then
30      open(unitprecip,file=path(2)(1:length(2))//'wetscav_precip.txt', &
31       form='formatted',err=998)
32  else
33      open(unitprecip,file=path(2)(1:length(2))//'wetscav_precip.txt', &
34       ACCESS='APPEND',form='formatted',err=998)
35  endif
36
37  jul=bdate+real(itime,kind=dp)/86400._dp
38  call caldate(jul,jjjjmmdd,ihmmss)
39  write(adate,'(i8.8)') jjjjmmdd
40  write(atime,'(i6.6)') ihmmss
41
42  do i=1,numpoint
43    xp1=xpoint1(i)*dx+xlon0 !lat, long (real) coord
44    yp1=ypoint1(i)*dy+ylat0 !lat, long (real) coord
45    ix=int((xpoint1(i)+xpoint2(i))/2.)
46    jy=int((ypoint1(i)+ypoint2(i))/2.)
47    write(unitprecip,*)  jjjjmmdd, ihmmss, &
48           xp1,yp1,lsprec(ix,jy,1,imem),convprec(ix,jy,1,imem) !time is the same as in the ECMWF windfield
49! units mm/h, valid for the time given in the windfield
50  end do
51
52  close(unitprecip)
53
54  return
55
56
57998   write(*,*) ' #### FLEXPART MODEL ERROR!   THE FILE         #### '
58  write(*,*) ' #### '//path(2)(1:length(2))//'header_txt'//' #### '
59  write(*,*) ' #### CANNOT BE OPENED. IF A FILE WITH THIS    #### '
60  write(*,*) ' #### NAME ALREADY EXISTS, DELETE IT AND START #### '
61  write(*,*) ' #### THE PROGRAM AGAIN.                       #### '
62  stop
63
64end subroutine writeprecip
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG