SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
dslt_init_names.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 dslt_init_names (KLUOUT, HRC1, HSV, KPMODE, &
7  keq, ksv_beg, ksv_end, ovarsig, orgfix)
8 !! ###########################################
9 !!
10 !!*** *DSLT_INIT_NAMES*
11 !!
12 !! PURPOSE
13 !! -------
14 !! Read and filter all chemical species into the CSV array
15 !! initialize NSV_CHSBEG and NSV_CHSEND index for the begin and the ending chemical index
16 !!
17 !!
18 !! REFERENCE
19 !! ---------
20 !! Modified ch_init_names (february 2005)
21 !!
22 !! AUTHOR
23 !! ------
24 !! Alf Grini <alf.grini@cnrm.meteo.fr>
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !!
29 !! EXTERNAL
30 !! --------
31 !!
32 !! IMPLICIT ARGUMENTS
33 !! ------------------
34 !-------------------------------------------------------------------------------
35 !
36 !* 0. DECLARATIONS
37 ! ------------
38 !
39 USE yomhook ,ONLY : lhook, dr_hook
40 USE parkind1 ,ONLY : jprb
41 !
42 IMPLICIT NONE
43 !
44 !* 0.1 declarations of arguments
45 !
46 INTEGER, INTENT(IN) :: kluout ! output listing channel
47  CHARACTER(LEN=4), INTENT(IN) :: hrc1
48  CHARACTER(LEN=*), DIMENSION(:), INTENT(IN) :: hsv ! name of chemical species
49  ! with character # for chemistry
50 INTEGER, INTENT(OUT) :: kpmode
51 INTEGER, INTENT(OUT) :: keq ! number of dust related variables
52 INTEGER, INTENT(OUT) :: ksv_beg ! first dust related scalar
53 INTEGER, INTENT(OUT) :: ksv_end ! last dust related scalar
54 LOGICAL, INTENT(INOUT) :: ovarsig ! type of standard deviation
55 LOGICAL, INTENT(INOUT) :: orgfix ! type of mean radius
56 !
57 !* 0.2 declarations of local variables
58 INTEGER :: jsv !! loop on scalar variables
59  CHARACTER(LEN=4) :: yrc1
60 REAL(KIND=JPRB) :: zhook_handle
61 !
62 !-------------------------------------------------------------------------------
63 
64 !Initialize output variables
65 IF (lhook) CALL dr_hook('DSLT_INIT_NAMES',0,zhook_handle)
66 !
67 keq = 0
68 ksv_beg = 0
69 ksv_end = 0
70 !
71 DO jsv=1, SIZE(hsv)
72  !
73  yrc1= hsv(jsv)(1:4)
74  !
75  IF (yrc1 == hrc1) THEN
76  !
77  IF (hsv(jsv)(5:5) == '6') ovarsig = .true.
78  IF (hsv(jsv)(5:5) == '0') orgfix = .false.
79  !
80  keq = keq + 1
81  IF (keq == 1) ksv_beg = jsv
82  !
83  ENDIF
84  !
85 ENDDO
86 !
87 ! Set the output list of scalar to the input list of scalars
88 !
89 ! Get the index of the last dust relevant tracer
90 ksv_end = ksv_beg + keq - 1
91 !
92 ! Get number of dust modes. Each mode represents
93 ! 3 moments, so 9 dust tracers represents 3 modes.
94 ! 3 dust tracers represents 1 mode
95 kpmode = ksv_end - ksv_beg + 1
96 IF (ovarsig) THEN
97  kpmode = int(kpmode / 3.)
98 ELSE IF (.NOT.orgfix) THEN
99  kpmode = int(kpmode / 2.)
100 END IF
101 !
102 IF (lhook) CALL dr_hook('DSLT_INIT_NAMES',1,zhook_handle)
103 !
104 END SUBROUTINE dslt_init_names
subroutine dslt_init_names(KLUOUT, HRC1, HSV, KPMODE, KEQ, KSV_BEG, KSV_END, OVARSIG, ORGFIX)