SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
modd_ch_emis_fieldn.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 ! ###########################
7 ! ###########################
8 !
9 !!**** *MODD_CH_EMIS_FIELD_n* - declaration of chemical emission data arrays
10 !!
11 !! PURPOSE
12 !! -------
13 ! The purpose of this declarative module is to specify the
14 ! chemical emission data arrays.
15 !
16 !!
17 !!** IMPLICIT ARGUMENTS
18 !! ------------------
19 !! None
20 !!
21 !! REFERENCE
22 !! ---------
23 !!
24 !!
25 !! AUTHOR
26 !! ------
27 !! D. Gazen *L.A.*
28 !!
29 !! MODIFICATIONS
30 !! -------------
31 !! Original 08/03/2001
32 !! 01/12/03 (D.Gazen) change emissions handling for surf. externalization
33 !-------------------------------------------------------------------------------
34 !
35 !* 0. DECLARATIONS
36 ! ------------
37 !
39 !
40 !
41 USE yomhook ,ONLY : lhook, dr_hook
42 USE parkind1 ,ONLY : jprb
43 !
44 IMPLICIT NONE
45 !
47 !
48  REAL :: XTIME_SIMUL = 0.
49  INTEGER :: NTIME_MAX
50  INTEGER :: NEMIS_NBR
51 ! ! number of chemical pgd fields chosen by user
52  CHARACTER(LEN=3) , DIMENSION(:), POINTER :: CEMIS_AREA
53 ! ! areas where chemical pgd fields are defined
54 ! ! 'ALL' : everywhere
55 ! ! 'SEA' : where sea exists
56 ! ! 'LAN' : where land exists
57 ! ! 'WAT' : where inland water exists
58 ! ! 'NAT' : where natural or agricultural areas exist
59 ! ! 'TWN' : where town areas exist
60 ! ! 'STR' : where streets are present
61 ! ! 'BLD' : where buildings are present
62 ! !
63  CHARACTER(LEN=40), DIMENSION(:), POINTER :: CEMIS_COMMENT ! comment
64  CHARACTER(LEN=40), DIMENSION(:), POINTER :: CEMIS_NAME
65 ! ! name of the chemical pgd fields (emitted species)
66 !
67  INTEGER, DIMENSION(:), POINTER :: NEMIS_TIME ! emission time
68 !
69  REAL, DIMENSION(:,:), POINTER:: XEMIS_FIELDS ! emission pgd fields values
70 !
71  INTEGER :: NEMISPEC_NBR ! Number of chemical species
72 !
73  TYPE(emissvar_t), DIMENSION(:), POINTER :: TSEMISS ! Offline emission struct array
74 !
75  TYPE(pronosvar_t), POINTER :: TSPRONOSLIST ! Head pointer on pronostic
76 ! variables list
77 !-------------------------------------------------------------------------------
78 !
79 END TYPE ch_emis_field_t
80 
81 
82 
83  CONTAINS
84 
85 !
86 
87 
88 
89 
90 SUBROUTINE ch_emis_field_init(YCH_EMIS_FIELD)
91 TYPE(ch_emis_field_t), INTENT(INOUT) :: ych_emis_field
92 REAL(KIND=JPRB) :: zhook_handle
93 IF (lhook) CALL dr_hook("MODD_CH_EMIS_FIELD_N:CH_EMIS_FIELD_INIT",0,zhook_handle)
94  nullify(ych_emis_field%CEMIS_AREA)
95  nullify(ych_emis_field%CEMIS_COMMENT)
96  nullify(ych_emis_field%CEMIS_NAME)
97  nullify(ych_emis_field%NEMIS_TIME)
98  nullify(ych_emis_field%XEMIS_FIELDS)
99  nullify(ych_emis_field%TSEMISS)
100 ych_emis_field%XTIME_SIMUL=0.
101 ych_emis_field%NEMIS_NBR=0
102 ych_emis_field%NTIME_MAX=-1
103 ych_emis_field%NEMISPEC_NBR=0
104 IF (lhook) CALL dr_hook("MODD_CH_EMIS_FIELD_N:CH_EMIS_FIELD_INIT",1,zhook_handle)
105 END SUBROUTINE ch_emis_field_init
106 
107 
108 END MODULE modd_ch_emis_field_n
109 
subroutine ch_emis_field_init(YCH_EMIS_FIELD)