source: flexpart.git/src/initial_cond_output_inversion.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: 6.9 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine initial_cond_output_inversion(itime)
5  !                                 i
6  !*****************************************************************************
7  !                                                                            *
8  !     Output of the initial condition sensitivity field.                     *
9  !                                                                            *
10  !     Author: A. Stohl                                                       *
11  !                                                                            *
12  !     24 May 1995                                                            *
13  !                                                                            *
14  !     13 April 1999, Major update: if output size is smaller, dump output    *
15  !                    in sparse matrix format; additional output of           *
16  !                    uncertainty                                             *
17  !                                                                            *
18  !     05 April 2000, Major update: output of age classes; output for backward*
19  !                    runs is time spent in grid cell times total mass of     *
20  !                    species.                                                *
21  !                                                                            *
22  !     17 February 2002, Appropriate dimensions for backward and forward runs *
23  !                       are now specified in file par_mod                    *
24  !                                                                            *
25  !     June 2006, write grid in sparse matrix with a single write command     *
26  !                in order to save disk space                                 *
27  !                                                                            *
28  !     2008 new sparse matrix format                                          *
29  !                                                                            *
30  !*****************************************************************************
31  !                                                                            *
32  ! Variables:                                                                 *
33  ! ncells          number of cells with non-zero concentrations               *
34  ! sparse          .true. if in sparse matrix format, else .false.            *
35  !                                                                            *
36  !*****************************************************************************
37
38  use unc_mod
39  use point_mod
40  use outg_mod
41  use par_mod
42  use com_mod
43
44  implicit none
45
46  integer :: itime,i,ix,jy,kz,ks,kp,sp_count_i,sp_count_r
47  integer :: jjjjmmdd, ihmmss
48  real(kind=dp) :: jul
49  real :: sp_fact,fact_recept
50  real,parameter :: smallnum = tiny(0.0) ! smallest number that can be handled
51  logical :: sp_zer,lexist
52  logical,save :: listart=.true.
53  logical,save,allocatable,dimension(:) :: listartrel
54  character :: adate*8,atime*6
55  character :: areldate*8,areltime*6
56  character(len=3) :: anspec
57
58  if(listart) then
59    allocate(listartrel(maxpointspec_act))
60    listartrel(:)=.true.
61  endif
62  print*, 'listartrel = ',listartrel
63
64  !*********************************************************************
65  ! Determine the standard deviation of the mean concentration or mixing
66  ! ratio (uncertainty of the output) and the dry and wet deposition
67  !*********************************************************************
68
69  do ks=1,nspec
70
71    write(anspec,'(i3.3)') ks
72
73    do kp=1,maxpointspec_act
74
75      ! calculate date of release
76      jul=bdate+real(ireleasestart(kp),kind=dp)/86400._dp    ! this is the current day
77      call caldate(jul,jjjjmmdd,ihmmss)
78      write(areldate,'(i8.8)') jjjjmmdd
79      write(areltime,'(i6.6)') ihmmss
80      print*, areldate//areltime
81
82      ! calculate date of field
83      jul=bdate+real(itime,kind=dp)/86400._dp
84      call caldate(jul,jjjjmmdd,ihmmss)
85      write(adate,'(i8.8)') jjjjmmdd
86      write(atime,'(i6.6)') ihmmss
87      print*, adate//atime
88
89      inquire(file=path(2)(1:length(2))//'grid_initial_'//areldate// &
90         areltime//'_'//anspec,exist=lexist)
91      if(lexist.and..not.listartrel(kp)) then
92        ! open and append to existing file
93        open(97,file=path(2)(1:length(2))//'grid_initial_'//areldate// &
94             areltime//'_'//anspec,form='unformatted',status='old',action='write',access='append')
95      else
96        ! open new file
97        open(97,file=path(2)(1:length(2))//'grid_initial_'//areldate// &
98             areltime//'_'//anspec,form='unformatted',status='replace',action='write')
99      endif
100      write(97) jjjjmmdd
101      write(97) ihmmss
102
103      listartrel(kp)=.false.
104
105      if (ind_rel.eq.1) then
106        fact_recept=rho_rel(kp)
107      else
108        fact_recept=1.
109      endif
110
111  !*******************************************************************
112  ! Generate output: may be in concentration (ng/m3) or in mixing
113  ! ratio (ppt) or both
114  ! Output the position and the values alternated multiplied by
115  ! 1 or -1, first line is number of values, number of positions
116  ! For backward simulations, the unit is seconds, stored in grid_time
117  !*******************************************************************
118
119  ! Write out dummy "wet and dry deposition" fields, to keep same format
120  ! as for concentration output
121!      sp_count_i=0
122!      sp_count_r=0
123!      write(97) sp_count_i
124!      write(97) (sparse_dump_i(i),i=1,sp_count_i)
125!      write(97) sp_count_r
126!      write(97) (sparse_dump_r(i),i=1,sp_count_r)
127!      write(97) sp_count_i
128!      write(97) (sparse_dump_i(i),i=1,sp_count_i)
129!      write(97) sp_count_r
130!      write(97) (sparse_dump_r(i),i=1,sp_count_r)
131
132
133  ! Write out sensitivity to initial conditions
134      sp_count_i=0
135      sp_count_r=0
136      sp_fact=-1.
137      sp_zer=.true.
138      do kz=1,numzgrid
139        do jy=0,numygrid-1
140          do ix=0,numxgrid-1
141            if (init_cond(ix,jy,kz,ks,kp).gt.smallnum) then
142              if (sp_zer.eqv..true.) then ! first non zero value
143                sp_count_i=sp_count_i+1
144                sparse_dump_i(sp_count_i)= &
145                     ix+jy*numxgrid+kz*numxgrid*numygrid
146                sp_zer=.false.
147                sp_fact=sp_fact*(-1.)
148              endif
149              sp_count_r=sp_count_r+1
150              sparse_dump_r(sp_count_r)=sp_fact* &
151                   init_cond(ix,jy,kz,ks,kp)/xmass(kp,ks)*fact_recept
152            else ! concentration is zero
153              sp_zer=.true.
154            endif
155          end do
156        end do
157      end do
158      write(97) sp_count_i
159      write(97) (sparse_dump_i(i),i=1,sp_count_i)
160      write(97) sp_count_r
161      write(97) (sparse_dump_r(i),i=1,sp_count_r)
162
163      close(97)
164
165    end do
166
167  end do
168
169  ! reset listart
170  if (listart) then
171    listart=.false.
172  endif
173
174end subroutine initial_cond_output_inversion
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG