source: flexpart.git/src/writeprecip.f90 @ 3481cc1

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

move license from headers to a different file

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