SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
ch_emission_snapn.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE ch_emission_snap_n (CHN, &
7  hprogram,ksize,psimtime,psuntime, &
8  kyear,kmonth,kday,prhoa,plon )
9 ! ######################################################################
10 !!
11 !!*** *CH_EMISSION_SNAP_n* -
12 !!
13 !! PURPOSE
14 !! -------
15 !! Return a time-dependent emission flux based on tabulated values
16 !!
17 !!** METHOD
18 !! ------
19 !!
20 !! AUTHOR
21 !! ------
22 !! S. Queguiner
23 !!
24 !! MODIFICATIONS
25 !! -------------
26 !! Original 10/2011
27 !!
28 !! EXTERNAL
29 !! --------
30 !!
31 !!
32 !! IMPLICIT ARGUMENTS
33 !! ------------------
34 !
36 !
37 USE modd_csts, ONLY: xday
38 !
39 USE modi_add_forecast_to_date_surf
40 USE modi_substract_to_date_surf
41 USE modi_ch_conversion_factor
42 !------------------------------------------------------------------------------
43 !
44 !* 0. DECLARATIONS
45 ! -----------------
46 !
47 USE yomhook ,ONLY : lhook, dr_hook
48 USE parkind1 ,ONLY : jprb
49 !
50 !
51 IMPLICIT NONE
52 !
53 !* 0.1 declaration of arguments
54 !
55 !
56 TYPE(ch_emis_snap_t), INTENT(INOUT) :: chn
57 !
58  CHARACTER(LEN=6), INTENT(IN) :: hprogram! program calling surf. schemes
59 INTEGER, INTENT(IN) :: ksize ! number of points
60 REAL, INTENT(IN) :: psimtime! time of simulation in sec UTC
61  ! (counting from midnight of
62  ! the current day)
63 REAL, DIMENSION(KSIZE), INTENT(IN) :: psuntime! Solar time (s since midnight)
64 INTEGER, INTENT(IN) :: kyear,kmonth,kday ! UTC year, month, day
65 REAL, DIMENSION(KSIZE), INTENT(IN) :: prhoa ! Air density
66 REAL, DIMENSION(KSIZE), INTENT(IN) :: plon ! Longitude (deg, from Greenwich)
67 ! ! (must be between -180deg and 180deg)
68 !
69 !* 0.2 declaration of local variables
70 !
71 REAL, DIMENSION(KSIZE) :: zlon ! Longitude centered in Greenwich meridian
72 REAL, DIMENSION(KSIZE) :: ztime0
73 INTEGER,DIMENSION(KSIZE,2) :: iyear ! Year at the begining of current hour
74 INTEGER,DIMENSION(KSIZE,2) :: imonth! Month at the begining of current hour
75 INTEGER,DIMENSION(KSIZE,2) :: iday ! Day at the begining of current hour
76 INTEGER,DIMENSION(KSIZE,2) :: idow ! Day of Week at the begining of current hour
77 INTEGER,DIMENSION(KSIZE,2) :: ihour ! Entire hour at the begining of current hour
78 REAL, DIMENSION(KSIZE,2) :: ztime ! time (s) at the begining of current hour
79 INTEGER :: jspec ! Loop counter on chemical species
80 INTEGER :: jsnap ! Loop counter on snap categories
81 INTEGER :: ji, jt ! Loop counter on points
82 REAL,DIMENSION(KSIZE,2) :: ze ! Emissions at beginning and end of the hour
83 !
84 REAL(KIND=JPRB) :: zhook_handle
85 !
86 !------------------------------------------------------------------------------
87 !
88 !* EXECUTABLE STATEMENTS
89 ! ---------------------
90 !
91 IF (lhook) CALL dr_hook('CH_EMISSION_SNAP_N',0,zhook_handle)
92 !
93 !------------------------------------------------------------------------------
94 !
95 !* 1. Updates Conversion Factor (may depends on air density)
96 ! ------------------------------------------------------
97 !
98  CALL ch_conversion_factor(chn, &
99  chn%CCONVERSION,prhoa(:))
100 !
101 !------------------------------------------------------------------------------
102 !
103 !* 2. time and date for each point depending on Time reference
104 ! --------------------------------------------------------
105 !
106 !* 2.1 time at the beginning of current hour
107 !
108 iday(:,1)=kday
109 imonth(:,1)=kmonth
110 iyear(:,1)=kyear
111 !
112 SELECT CASE (chn%CSNAP_TIME_REF)
113  CASE ('UTC ')
114  ztime0(:)=psimtime
115  CASE ('SOLAR')
116  zlon(:)=plon(:)
117  WHERE(plon(:)> 180.) zlon(:)=plon(:)-360.
118  WHERE(plon(:)<=-180.) zlon(:)=plon(:)+360.
119  !* retrieves solar date and time
120  ztime0(:)=psimtime + zlon(:)*240. ! first guess is approximated solar time.
121  ! The suntime should be close to this.
122  DO ji=1,ksize
123  IF (ztime0(ji)>psuntime(ji)+xday/2.) THEN
124  ztime0(ji) = psuntime(ji) + xday
125  ELSEIF (ztime0(ji)<psuntime(ji)-xday/2.) THEN
126  ztime0(ji) = psuntime(ji) - xday
127  ELSE
128  ztime0(ji) = psuntime(ji)
129  END IF
130  CALL add_forecast_to_date_surf(iyear(ji,1),imonth(ji,1),iday(ji,1),ztime0(ji))
131  CALL substract_to_date_surf(iyear(ji,1),imonth(ji,1),iday(ji,1),ztime0(ji))
132  ENDDO
133 
134  CASE ('LEGAL')
135  ztime0(:)=psimtime + chn%XDELTA_LEGAL_TIME(:) * 3600.
136  DO ji=1,ksize
137  CALL add_forecast_to_date_surf(iyear(ji,1),imonth(ji,1),iday(ji,1),ztime0(ji))
138  CALL substract_to_date_surf(iyear(ji,1),imonth(ji,1),iday(ji,1),ztime0(ji))
139  ENDDO
140 
141 END SELECT
142 !
143  CALL day_of_week(iday(:,1), imonth(:,1), iyear(:,1), idow(:,1))
144 !
145 ihour(:,1) = int((ztime0(:)+1.e-10)/3600.)! 1.E-10 and the where condition after are
146 WHERE (ihour(:,1)==24) ihour(:,1)=23 ! set to avoid computer precision problems
147 ztime(:,1) = ihour(:,1) * 3600.
148 !
149 !* 2.2 time at the end of current hour
150 !
151 iday(:,2)=iday(:,1)
152 imonth(:,2)=imonth(:,1)
153 iyear(:,2)=iyear(:,1)
154 !
155 ztime(:,2) = (ihour(:,1)+1) * 3600.
156 !
157 DO ji=1,ksize
158  CALL add_forecast_to_date_surf(iyear(ji,2),imonth(ji,2),iday(ji,2),ztime(ji,2))
159 ENDDO
160 !
161  CALL day_of_week(iday(:,2), imonth(:,2), iyear(:,2), idow(:,2))
162 !
163 ihour(:,2)=nint(ztime(:,2))/3600
164 !
165 !------------------------------------------------------------------------------
166 !
167 !* 3. Emission at the begining of the current hour
168 ! --------------------------------------------
169 !
170  chn%XEMIS_FIELDS(:,:)=0.
171 !
172 DO jspec=1,chn%NEMIS_NBR
173  !
174  ze(:,:) = 0.
175  !
176  DO jsnap=1,chn%NEMIS_SNAP
177  !
178  DO jt=1,2
179  !
180  DO ji=1,ksize
181  !
182  ze(ji,jt) = ze(ji,jt) + chn%XEMIS_FIELDS_SNAP(ji,jsnap,jspec) &
183  *chn%XSNAP_MONTHLY(imonth(ji,jt) ,jsnap,jspec) &
184  *chn%XSNAP_DAILY (idow(ji,jt) ,jsnap,jspec) &
185  *chn%XSNAP_HOURLY (ihour(ji,jt)+1,jsnap,jspec) &
186  *chn%XCONVERSION(ji)
187  ENDDO
188  !
189  ENDDO
190  !
191  ENDDO
192 !
193 !* 5. Temporal interpolation within the current hour
194 ! ----------------------------------------------
195 !
196  chn%XEMIS_FIELDS(:,jspec) = ze(:,1) + (ze(:,2)-ze(:,1))/3600.*(ztime0(:)-ihour(:,1)*3600.)
197 
198 END DO
199 !
200 IF (lhook) CALL dr_hook('CH_EMISSION_SNAP_N',1,zhook_handle)
201 !
202 !-------------------------------------------------------------------------------
203  CONTAINS
204 !
205 SUBROUTINE day_of_week(DATE, MONTH, YEAR, DOW)
206 !! AUTHOR
207 !! ------
208 !! J.Arteta
209 !! Original August 2010
210 !!
211 !!
212 !! MODifICATIONS
213 !! -------------
214 !! S. Queguiner 10/2011 DAY:Monday->Sunday => DOW:1->7
215 !
216 IMPLICIT NONE
217 INTEGER, DIMENSION(:), INTENT(IN) :: date, month, year
218 INTEGER, DIMENSION(:), INTENT(OUT):: dow
219 INTEGER, DIMENSION(SIZE(DOW)) :: day, yr, mn, n1, n2
220 REAL(KIND=JPRB) :: zhook_handle
221 !
222 IF (lhook) CALL dr_hook('CH_EMISSION_SNAP_N:DAY_OF_WEEK',0,zhook_handle)
223 !
224 yr = year
225 mn = month
226 !
227 WHERE (mn.LE.2)
228  mn = mn + 12
229  yr = yr -1
230 END WHERE
231 !
232 n1 = (26 * (mn + 1)) /10
233 n2 = (125 * yr) / 100
234 day = (date + n1 + n2 - (yr / 100) + (yr / 400) - 1)
235 !
236 dow = mod(day,7) + 7
237 WHERE (dow.GT.7) dow = dow - 7
238 !
239 IF (lhook) CALL dr_hook('CH_EMISSION_SNAP_N:DAY_OF_WEEK',1,zhook_handle)
240 END SUBROUTINE day_of_week
241 !
242 END SUBROUTINE ch_emission_snap_n
subroutine ch_conversion_factor(CHN, HCONVERSION, PRHOA)
subroutine day_of_week(DATE, MONTH, YEAR, DOW)
subroutine add_forecast_to_date_surf(KYEAR, KMONTH, KDAY, PSEC)
subroutine substract_to_date_surf(KYEAR, KMONTH, KDAY, PSEC)
subroutine ch_emission_snap_n(CHN, HPROGRAM, KSIZE, PSIMTIME, PSUNTIME, KYEAR, KMONTH, KDAY, PRHOA, PLON)