SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
write_diag_ch_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 write_diag_ch_snap_n (DTCO, DGU, U, CHN, &
7  hprogram)
8 ! #################################
9 !
10 !!**** *WRITE_DIAG_CH_SNAP_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 !! M.Leriche 04/2014 change emissions name EMIS_ -> E_ name for coherence with PGD
32 !! change length of CHARACTER for emission 6->12
33 !!-------------------------------------------------------------------------------
34 !
35 !* 0. DECLARATIONS
36 ! ------------
37 !
40 USE modd_surf_atm_n, ONLY : surf_atm_t
42 !
43 USE modd_csts, ONLY : xavogadro
44 USE modi_init_io_surf_n
46 USE modi_end_io_surf_n
47 !
48 !
49 USE yomhook ,ONLY : lhook, dr_hook
50 USE parkind1 ,ONLY : jprb
51 !
52 IMPLICIT NONE
53 !
54 !* 0.1 Declarations of arguments
55 ! -------------------------
56 !
57 !
58 TYPE(data_cover_t), INTENT(INOUT) :: dtco
59 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
60 TYPE(surf_atm_t), INTENT(INOUT) :: u
61 TYPE(ch_emis_snap_t), INTENT(INOUT) :: chn
62 !
63  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
64 !
65 !* 0.2 Declarations of local variables
66 ! -------------------------------
67 !
68 
69 INTEGER :: iresp ! IRESP : return-code if a problem appears
70  CHARACTER(LEN=16) :: yrecfm ! Name of the article to be read
71  CHARACTER(LEN=100):: ycomment ! Comment string
72 !
73 INTEGER :: jspec
74 REAL(KIND=JPRB) :: zhook_handle
75 !
76 !-------------------------------------------------------------------------------
77 !
78 ! Initialisation for IO
79 !
80 IF (lhook) CALL dr_hook('WRITE_DIAG_CH_SNAP_n',0,zhook_handle)
81  CALL init_io_surf_n(dtco, dgu, u, &
82  hprogram,'FULL ','SURF ','WRITE')
83 !
84 !-------------------------------------------------------------------------------
85 !
86 ! Writes Emissions of all species
87 !
88 DO jspec=1,chn%NEMIS_NBR
89  yrecfm = "E_"//trim(chn%CEMIS_NAME(jspec))
90  ycomment = "Emission data at time t (ppm*m/s)"
91  CALL write_surf(dgu, u, &
92  hprogram,yrecfm,chn%XEMIS_FIELDS(:,jspec),iresp,hcomment=ycomment)
93 END DO
94 !
95 !-------------------------------------------------------------------------------
96 !
97 ! End of IO
98 !
99  CALL end_io_surf_n(hprogram)
100 IF (lhook) CALL dr_hook('WRITE_DIAG_CH_SNAP_n',1,zhook_handle)
101 !
102 !
103 END SUBROUTINE write_diag_ch_snap_n
subroutine init_io_surf_n(DTCO, DGU, U, HPROGRAM, HMASK, HSCHEME, HACTION)
subroutine write_diag_ch_snap_n(DTCO, DGU, U, CHN, HPROGRAM)
subroutine end_io_surf_n(HPROGRAM)
Definition: end_io_surfn.F90:6