source: flexpart.git/src/initial_cond_output.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: 5.3 KB
Line 
1subroutine initial_cond_output(itime)
2  !                                 i
3  !*****************************************************************************
4  !                                                                            *
5  !     Output of the initial condition sensitivity field.                     *
6  !                                                                            *
7  !     Author: A. Stohl                                                       *
8  !                                                                            *
9  !     24 May 1995                                                            *
10  !                                                                            *
11  !     13 April 1999, Major update: if output size is smaller, dump output    *
12  !                    in sparse matrix format; additional output of           *
13  !                    uncertainty                                             *
14  !                                                                            *
15  !     05 April 2000, Major update: output of age classes; output for backward*
16  !                    runs is time spent in grid cell times total mass of     *
17  !                    species.                                                *
18  !                                                                            *
19  !     17 February 2002, Appropriate dimensions for backward and forward runs *
20  !                       are now specified in file par_mod                    *
21  !                                                                            *
22  !     June 2006, write grid in sparse matrix with a single write command     *
23  !                in order to save disk space                                 *
24  !                                                                            *
25  !     2008 new sparse matrix format                                          *
26  !                                                                            *
27  !*****************************************************************************
28  !                                                                            *
29  ! Variables:                                                                 *
30  ! ncells          number of cells with non-zero concentrations               *
31  ! sparse          .true. if in sparse matrix format, else .false.            *
32  !                                                                            *
33  !*****************************************************************************
34
35  use unc_mod
36  use point_mod
37  use outg_mod
38  use par_mod
39  use com_mod
40
41  implicit none
42
43  integer :: itime,i,ix,jy,kz,ks,kp,sp_count_i,sp_count_r
44  real :: sp_fact,fact_recept
45  real,parameter :: smallnum = tiny(0.0) ! smallest number that can be handled
46  logical :: sp_zer
47  character(len=3) :: anspec
48
49
50  !*********************************************************************
51  ! Determine the standard deviation of the mean concentration or mixing
52  ! ratio (uncertainty of the output) and the dry and wet deposition
53  !*********************************************************************
54
55  do ks=1,nspec
56
57    write(anspec,'(i3.3)') ks
58    open(97,file=path(2)(1:length(2))//'grid_initial'// &
59         '_'//anspec,form='unformatted')
60    write(97) itime
61
62    do kp=1,maxpointspec_act
63
64      if (ind_rel.eq.1) then
65        fact_recept=rho_rel(kp)
66      else
67        fact_recept=1.
68      endif
69
70  !*******************************************************************
71  ! Generate output: may be in concentration (ng/m3) or in mixing
72  ! ratio (ppt) or both
73  ! Output the position and the values alternated multiplied by
74  ! 1 or -1, first line is number of values, number of positions
75  ! For backward simulations, the unit is seconds, stored in grid_time
76  !*******************************************************************
77
78  ! Write out dummy "wet and dry deposition" fields, to keep same format
79  ! as for concentration output
80      sp_count_i=0
81      sp_count_r=0
82      write(97) sp_count_i
83      write(97) (sparse_dump_i(i),i=1,sp_count_i)
84      write(97) sp_count_r
85      write(97) (sparse_dump_r(i),i=1,sp_count_r)
86      write(97) sp_count_i
87      write(97) (sparse_dump_i(i),i=1,sp_count_i)
88      write(97) sp_count_r
89      write(97) (sparse_dump_r(i),i=1,sp_count_r)
90
91
92  ! Write out sensitivity to initial conditions
93      sp_count_i=0
94      sp_count_r=0
95      sp_fact=-1.
96      sp_zer=.true.
97      do kz=1,numzgrid
98        do jy=0,numygrid-1
99          do ix=0,numxgrid-1
100            if (init_cond(ix,jy,kz,ks,kp).gt.smallnum) then
101              if (sp_zer.eqv..true.) then ! first non zero value
102                sp_count_i=sp_count_i+1
103                sparse_dump_i(sp_count_i)= &
104                     ix+jy*numxgrid+kz*numxgrid*numygrid
105                sp_zer=.false.
106                sp_fact=sp_fact*(-1.)
107              endif
108              sp_count_r=sp_count_r+1
109              sparse_dump_r(sp_count_r)=sp_fact* &
110                   init_cond(ix,jy,kz,ks,kp)/xmass(kp,ks)*fact_recept
111            else ! concentration is zero
112              sp_zer=.true.
113            endif
114          end do
115        end do
116      end do
117      write(97) sp_count_i
118      write(97) (sparse_dump_i(i),i=1,sp_count_i)
119      write(97) sp_count_r
120      write(97) (sparse_dump_r(i),i=1,sp_count_r)
121
122
123    end do
124
125    close(97)
126
127  end do
128
129
130end subroutine initial_cond_output
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG