SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
writesurf_ch_emisn.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 writesurf_ch_emis_n (DGU, U, &
7  che, &
8  hprogram)
9 ! ##########################################################
10 !
11 !!**** *WRITESURF_CH_EMIS_n* - routine to write chemistry emission fields
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !! AUTHOR
17 !! ------
18 !! V. Masson *Meteo France*
19 !!
20 !! MODIFICATIONS
21 !! -------------
22 !! Original 03/2004
23 !-------------------------------------------------------------------------------
24 !
25 !* 0. DECLARATIONS
26 ! ------------
27 !
28 !
29 !
30 !
32 USE modd_surf_atm_n, ONLY : surf_atm_t
33 !
35 !
37 !
38 !
39 USE yomhook ,ONLY : lhook, dr_hook
40 USE parkind1 ,ONLY : jprb
41 !
42 USE modi_abor1_sfx
43 !
44 IMPLICIT NONE
45 !
46 !* 0.1 Declarations of arguments
47 ! -------------------------
48 !
49 !
50 !
51 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
52 TYPE(surf_atm_t), INTENT(INOUT) :: u
53 !
54 TYPE(ch_emis_field_t), INTENT(INOUT) :: che
55 !
56  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
57 !
58 !* 0.2 Declarations of local variables
59 ! -------------------------------
60 !
61 INTEGER :: iresp ! IRESP : return-code if a problem appears
62  ! at the open of the file in LFI routines
63 !
64  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be written
65  CHARACTER(LEN=100):: ycomment ! Comment string
66  CHARACTER(LEN=80) :: yname ! emitted species name
67 !
68 INTEGER :: ji,jt ! loop indices
69 INTEGER :: jspec ! loop index
70 LOGICAL :: gfound,lok
71  CHARACTER(LEN=40),DIMENSION(CHE%NEMIS_NBR) :: yemispec_names
72 INTEGER, DIMENSION(CHE%NEMIS_NBR) :: inbtimes
73 INTEGER, DIMENSION(CHE%NEMIS_NBR) :: ifirst,ilast,inext
74 INTEGER :: intimesmax,itmp
75 INTEGER :: iemispec_nbr
76 REAL(KIND=JPRB) :: zhook_handle
77 
78 !-------------------------------------------------------------------------------
79 !
80 !* 1. Chemical Emission fields :
81 ! --------------------------
82 !
83 IF (lhook) CALL dr_hook('WRITESURF_CH_EMIS_N',0,zhook_handle)
84 yrecfm='EMISFILE_NBR'
85 ycomment='Total number of 2D emission files.'
86  CALL write_surf(dgu, u, &
87  hprogram,yrecfm,che%NEMIS_NBR,iresp,hcomment=ycomment)
88 !
89 ! count emitted species
90 iemispec_nbr = 0
91 DO ji=1,che%NEMIS_NBR
92  yname = trim(adjustl(che%CEMIS_NAME(ji)))
93  gfound = .false.
94  DO jspec = 1,iemispec_nbr
95  IF (yemispec_names(jspec) == yname) THEN
96  gfound = .true.
97  EXIT
98  END IF
99  END DO
100  IF (.NOT. gfound) THEN
101  iemispec_nbr = iemispec_nbr+1
102  yemispec_names(iemispec_nbr) = yname
103  inbtimes(iemispec_nbr) = 1
104  ifirst(iemispec_nbr) = ji
105  ilast(iemispec_nbr) = ji
106  inext(ji) = 0
107  ELSE
108  inext(ilast(jspec)) = ji
109  inext(ji) = 0
110  ilast(jspec) = ji
111  inbtimes(jspec) = inbtimes(jspec)+1
112  END IF
113 END DO
114 !
115 yrecfm='EMISPEC_NBR '
116 ycomment='Number of emitted chemical species.'
117  CALL write_surf(dgu, u, &
118  hprogram,yrecfm,iemispec_nbr,iresp,hcomment=ycomment)
119 !
120 IF (iemispec_nbr > 0) THEN
121  !
122  DO jspec = 1,iemispec_nbr
123  CALL write_emis_spec(inbtimes(jspec))
124  ENDDO
125  !
126 ENDIF
127 !
128 IF (lhook) CALL dr_hook('WRITESURF_CH_EMIS_N',1,zhook_handle)
129 !
130 !-------------------------------------------------------------------------------
131  CONTAINS
132 !
133 SUBROUTINE write_emis_spec(KSIZE)
134 !
135 INTEGER, INTENT(IN) :: ksize
136 INTEGER,DIMENSION(KSIZE) :: itime
137 INTEGER,DIMENSION(KSIZE) :: iindex
138 REAL,DIMENSION(SIZE(CHE%XEMIS_FIELDS,1),KSIZE) :: zwork2d
139 REAL(KIND=JPRB) :: zhook_handle
140 !
141 IF (lhook) CALL dr_hook('WRITESURF_CH_EMIS_N:WRITE_EMIS_SPEC',0,zhook_handle)
142 !
143 ji = ifirst(jspec)
144 jt = 0
145 ! fill the emission times array (ITIME)
146 ! and the corresponding indices array (IINDEX)
147 ! for species number JSPEC
148 DO WHILE(ji /= 0)
149  jt = jt+1
150  itime(jt) = che%NEMIS_TIME(ji)
151  iindex(jt) = ji
152  ji = inext(ji)
153 END DO
154 IF (jt /= ksize) THEN
155  CALL abor1_sfx('WRITESURF_CH_EMISN: ABNORMAL ERROR')
156 END IF
157 ! sort indices according to ITIME values
158 lok = .true.
159 DO WHILE (lok)
160  lok = .false.
161  DO ji=2,ksize
162  IF (itime(ji-1) > itime(ji)) THEN
163  lok = .true.
164  itmp = itime(ji-1)
165  itime(ji-1) = itime(ji)
166  itime(ji) = itmp
167  itmp = iindex(ji-1)
168  iindex(ji-1) = iindex(ji)
169  iindex(ji) = itmp
170  END IF
171  END DO
172 END DO
173 ! Now fill the ZWORK2D array for writing
174 zwork2d(:,:) = che%XEMIS_FIELDS(:,iindex(:))
175 !
176 ! Write NAME of species JSPEC with AREA and number of emission times
177 ! stored in the commentary
178 WRITE(yrecfm,'("EMISNAME",I3.3)') jspec
179 WRITE(ycomment,'(A3,", emission times number:",I5)') che%CEMIS_AREA(iindex(1)),ksize
180  CALL write_surf(dgu, u, &
181  hprogram,yrecfm,yemispec_names(jspec),iresp,hcomment=ycomment)
182 !
183 WRITE(yrecfm,'("EMISAREA",I3.3)') jspec
184 ycomment = "Emission area"
185  CALL write_surf(dgu, u, &
186  hprogram,yrecfm,che%CEMIS_AREA(iindex(1)),iresp,hcomment=ycomment)
187 !
188 WRITE(yrecfm,'("EMISNBT",I3.3)') jspec
189 ycomment = "Emission times number"
190  CALL write_surf(dgu, u, &
191  hprogram,yrecfm,ksize,iresp,hcomment=ycomment)
192 
193 ! Write emission times (ITIME) for species JSPEC
194 WRITE(yrecfm,'("EMISTIMES",I3.3)') jspec
195 ycomment = "Emission times in second"
196  CALL write_surf(dgu, u, &
197  hprogram,yrecfm,itime(:),iresp,hcomment=ycomment,hdir='-',hnam_dim="Temporal_emiss ")
198 !
199 ! Finally write emission data for species JSPEC
200 yrecfm = "E_"//trim(yemispec_names(jspec))
201 ycomment = "Emission data (x,y,t),"//trim(che%CEMIS_COMMENT(iindex(1)))
202  CALL write_surf(dgu, u, &
203  hprogram,yrecfm,zwork2d(:,:),iresp,hcomment=ycomment,hnam_dim="Temporal_emiss ")
204 !
205 IF (lhook) CALL dr_hook('WRITESURF_CH_EMIS_N:WRITE_EMIS_SPEC',1,zhook_handle)
206 !
207 END SUBROUTINE write_emis_spec
208 !
209 END SUBROUTINE writesurf_ch_emis_n
subroutine writesurf_ch_emis_n(DGU, U, CHE, HPROGRAM)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine write_emis_spec(KSIZE)