SURFEX v8.1
General documentation of Surfex
modd_dstn.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 MODULE modd_dst_n
6 
7 !Purpose:
8 !Declare variables and constants necessary to do the dust calculations
9 !Here are only the variables which depend on the grid!
10 
11 !Author: Alf Grini <alf.grini@cnrm.meteo.fr>
12 
13 !
14 USE yomhook ,ONLY : lhook, dr_hook
15 USE parkind1 ,ONLY : jprb
16 !
17 IMPLICIT NONE
18 
19 TYPE dst_t
20  !
21  INTEGER, DIMENSION(:), POINTER :: nvt_dst !MASK: dust vegetation number to vegetation number
22  INTEGER, DIMENSION(:), POINTER :: nsize_patch_dst !Number of points for a patch and a vegetation class
23  INTEGER, DIMENSION(:,:), POINTER :: nr_patch_dst !Mask from patch-points to dust-points
24  REAL,DIMENSION(:), POINTER :: z0_erod_dst !Roughness length momentum over erodible dust emitter sfc
25  CHARACTER(LEN=6), DIMENSION(:), POINTER :: csv_dst !Name of scalar variables
26  REAL, DIMENSION(:,:),POINTER :: xsfdst !Dust variables to be send to output
27  REAL, DIMENSION(:,:),POINTER :: xsfdstm !Dust variables to be send to output
28  REAL,DIMENSION(:), POINTER :: xemisradius_dst !Number median radius for each source mode
29  REAL,DIMENSION(:), POINTER :: xemissig_dst !sigma for each source mode
30  REAL,DIMENSION(:), POINTER :: xmss_frc_src !Mass fraction of each source mode
31  !
32 END TYPE dst_t
33 !
35 !
36 TYPE(dst_t), DIMENSION(:), POINTER :: al=>null()
37 !
38 END TYPE dst_np_t
39 !
40 CONTAINS
41 !
42 SUBROUTINE dst_init(YDST)
43 TYPE(dst_t), INTENT(INOUT) :: YDST
44 REAL(KIND=JPRB) :: ZHOOK_HANDLE
45 IF (lhook) CALL dr_hook("MODD_DST_N:DST_INIT",0,zhook_handle)
46  NULLIFY(ydst%NVT_DST)
47  NULLIFY(ydst%NSIZE_PATCH_DST)
48  NULLIFY(ydst%NR_PATCH_DST)
49  NULLIFY(ydst%Z0_EROD_DST)
50  NULLIFY(ydst%CSV_DST)
51  NULLIFY(ydst%XSFDST)
52  NULLIFY(ydst%XSFDSTM)
53  NULLIFY(ydst%XEMISRADIUS_DST)
54  NULLIFY(ydst%XEMISSIG_DST)
55  NULLIFY(ydst%XMSS_FRC_SRC)
56 IF (lhook) CALL dr_hook("MODD_DST_N:DST_INIT",1,zhook_handle)
57 END SUBROUTINE dst_init
58 !
59 SUBROUTINE dst_np_init(YDST_NP,KPATCH)
60 TYPE(dst_np_t), INTENT(INOUT) :: YDST_NP
61 INTEGER, INTENT(IN) :: KPATCH
62 INTEGER :: JP
63 REAL(KIND=JPRB) :: ZHOOK_HANDLE
64 !
65 IF (lhook) CALL dr_hook("MODD_DST_N:DST_NP_INIT",0,zhook_handle)
66 !
67 IF (ASSOCIATED(ydst_np%AL)) THEN
68  DO jp = 1,kpatch
69  CALL dst_init(ydst_np%AL(jp))
70  ENDDO
71  DEALLOCATE(ydst_np%AL)
72 ELSE
73  ALLOCATE(ydst_np%AL(kpatch))
74  DO jp = 1,kpatch
75  CALL dst_init(ydst_np%AL(jp))
76  ENDDO
77 ENDIF
78 !
79 IF (lhook) CALL dr_hook("MODD_DST_N:DST_NP_INIT",1,zhook_handle)
80 !
81 END SUBROUTINE dst_np_init
82 !
83 END MODULE modd_dst_n
integer, parameter jprb
Definition: parkind1.F90:32
subroutine dst_init(YDST)
Definition: modd_dstn.F90:43
logical lhook
Definition: yomhook.F90:15
subroutine dst_np_init(YDST_NP, KPATCH)
Definition: modd_dstn.F90:60