SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
write_diag_ch_aggr.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 write_diag_ch_aggr_n (DTCO, DGU, U, CHE, &
7  hprogram)
8 ! #################################
9 !
10 !!**** *WRITE_DIAG_CH_AGGR_n* - writes surface chemical emissions diagnostics
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!
16 !!** METHOD
17 !! ------
18 !!
19 !!
20 !! REFERENCE
21 !! ---------
22 !!
23 !!
24 !! AUTHOR
25 !! ------
26 !! V. Masson & S. Queguiner *Meteo France*
27 !!
28 !! MODIFICATIONS
29 !! -------------
30 !! Original 01/2012
31 !!-------------------------------------------------------------------------------
32 !
33 !* 0. DECLARATIONS
34 ! ------------
35 !
36 !
39 USE modd_surf_atm_n, ONLY : surf_atm_t
41 !
42 USE modd_csts, ONLY : xavogadro
43 USE modi_init_io_surf_n
45 USE modi_end_io_surf_n
46 !
47 !
48 USE yomhook ,ONLY : lhook, dr_hook
49 USE parkind1 ,ONLY : jprb
50 !
51 IMPLICIT NONE
52 !
53 !* 0.1 Declarations of arguments
54 ! -------------------------
55 !
56 !
57 TYPE(data_cover_t), INTENT(INOUT) :: dtco
58 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
59 TYPE(surf_atm_t), INTENT(INOUT) :: u
60 TYPE(ch_emis_field_t), INTENT(INOUT) :: che
61 !
62  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
63 !
64 !* 0.2 Declarations of local variables
65 ! -------------------------------
66 !
67 
68 INTEGER :: iresp ! IRESP : return-code if a problem appears
69  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
70  CHARACTER(LEN=100):: ycomment ! Comment string
71 !
72 INTEGER :: jspec
73 REAL(KIND=JPRB) :: zhook_handle
74 !
75 !-------------------------------------------------------------------------------
76 !
77 ! Initialisation for IO
78 !
79 IF (lhook) CALL dr_hook('WRITE_DIAG_CH_AGGR_n',0,zhook_handle)
80  CALL init_io_surf_n(dtco, dgu, u, &
81  hprogram,'FULL ','SURF ','WRITE')
82 !
83 !-------------------------------------------------------------------------------
84 !
85 ! Writes Emissions of all species
86 !
87 DO jspec=1,SIZE(che%TSEMISS)
88  yrecfm = "E_"//trim(che%TSEMISS(jspec)%CNAME)
89  ycomment = "Emission data at time t (ppm*m/s)"
90  CALL write_surf(dgu, u, &
91  hprogram,yrecfm,che%TSEMISS(jspec)%XEMISDATA,iresp,hcomment=ycomment)
92 END DO
93 !
94 !-------------------------------------------------------------------------------
95 !
96 ! End of IO
97 !
98  CALL end_io_surf_n(hprogram)
99 IF (lhook) CALL dr_hook('WRITE_DIAG_CH_AGGR_n',1,zhook_handle)
100 !
101 !
102 END SUBROUTINE write_diag_ch_aggr_n
subroutine init_io_surf_n(DTCO, DGU, U, HPROGRAM, HMASK, HSCHEME, HACTION)
subroutine end_io_surf_n(HPROGRAM)
Definition: end_io_surfn.F90:6
subroutine write_diag_ch_aggr_n(DTCO, DGU, U, CHE, HPROGRAM)