SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
dslt_init_modes.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_modes (KEQ, KSV_BEG, KSV_END, OVARSIG, ORGFIX, &
7  kmdebeg, kmde)
8 !! ###########################################
9 !!
10 !!*** *DSLT_INIT_MODES*
11 !!
12 !! PURPOSE
13 !! -------
14 !! Find the number of dust modes to be transported
15 !! Each mode needs 3 moments to be described, so logically, the number of modes is
16 !! The number of dust tracers divided by 3
17 !!
18 !!
19 !! REFERENCE
20 !! ---------
21 !! Modified dst_init_names (march 2005)
22 !!
23 !! AUTHOR
24 !! ------
25 !! Alf Grini <alf.grini@cnrm.meteo.fr>
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !!
30 !! EXTERNAL
31 !! --------
32 !!
33 !! IMPLICIT ARGUMENTS
34 !! ------------------
35 !-------------------------------------------------------------------------------
36 !
37 !* 0. DECLARATIONS
38 ! ------------
39 !
40 USE yomhook ,ONLY : lhook, dr_hook
41 USE parkind1 ,ONLY : jprb
42 !
43 USE modi_abor1_sfx
44 !
45 IMPLICIT NONE
46 !
47 !* 0.1 declarations of arguments
48 !
49 
50 INTEGER, INTENT(IN) :: keq ! number of dust variables
51 INTEGER, INTENT(IN) :: ksv_beg ! First number of dust tracer
52 INTEGER, INTENT(IN) :: ksv_end ! Last number of dust tracer
53 LOGICAL, INTENT(IN) :: ovarsig ! type of standard deviation (fixed or variable)
54 LOGICAL, INTENT(IN) :: orgfix ! type of mean radius
55 INTEGER, INTENT(OUT) :: kmdebeg ! Place in scalar list of dustmass in first mode
56 INTEGER, INTENT(OUT) :: kmde ! Number of dust modes
57 REAL(KIND=JPRB) :: zhook_handle
58 
59 
60 !Check if you have a multiple of 3 dust related variables, and
61 !Set the number of modes to the number of dust related variables
62 !divided by 3
63 IF (lhook) CALL dr_hook('DSLT_INIT_MODES',0,zhook_handle)
64 !
65 kmdebeg = ksv_beg
66 kmde = ksv_end - ksv_beg + 1
67 !
68 IF (ovarsig) THEN !case three moments by modes
69  IF(mod(kmde,3).NE.0.) THEN
70  CALL abor1_sfx('DST_INIT_MODES: (1) WRONG NUMBER OF DUST VARIABLES')
71  ELSE
72  kmde = kmde / 3
73  ENDIF
74 ELSE IF (.NOT.orgfix) THEN ! case two moment by modes
75  IF(mod(kmde,2).ne.0.)THEN
76  CALL abor1_sfx('DST_INIT_MODES: (1) WRONG NUMBER OF DUST VARIABLES')
77  ELSE
78  kmde = kmde / 2
79  END IF
80 END IF
81 !
82 IF (lhook) CALL dr_hook('DSLT_INIT_MODES',1,zhook_handle)
83 !
84 END SUBROUTINE dslt_init_modes
subroutine dslt_init_modes(KEQ, KSV_BEG, KSV_END, OVARSIG, ORGFIX, KMDEBEG, KMDE)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6