SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
get_type_dimn.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 get_type_dim_n (DTCO, U, &
7  htype,kdim)
8 ! #####################################
9 !
10 !!**** *GET_TYPE_DIM_n* - routine to get the number of point for any surface type
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!** METHOD
16 !! -------
17 !!
18 !! REFERENCE
19 !! ---------
20 !!
21 !!
22 !! AUTHOR
23 !! ------
24 !! V. Masson *Meteo France*
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 01/2004
29 !-------------------------------------------------------------------------------
30 !
31 !* 0. DECLARATIONS
32 ! ------------
33 !
34 !
35 !
36 !
38 USE modd_surf_atm_n, ONLY : surf_atm_t
39 !
40 USE modi_convert_cover_frac
41 !
42 !
43 USE yomhook ,ONLY : lhook, dr_hook
44 USE parkind1 ,ONLY : jprb
45 !
46 IMPLICIT NONE
47 !
48 !* 0.1 Declarations of arguments
49 ! -------------------------
50 !
51 !
52 TYPE(data_cover_t), INTENT(INOUT) :: dtco
53 TYPE(surf_atm_t), INTENT(INOUT) :: u
54 !
55  CHARACTER(LEN=6), INTENT(IN) :: htype ! Type of surface
56 INTEGER, INTENT(INOUT) :: kdim ! size of the mask
57 !
58 !* 0.2 Declarations of local variables
59 ! -------------------------------
60 !
61 REAL, DIMENSION(:), ALLOCATABLE :: zsea ! sea cover
62 REAL, DIMENSION(:), ALLOCATABLE :: znature! nature cover
63 REAL, DIMENSION(:), ALLOCATABLE :: ztown ! town cover
64 REAL, DIMENSION(:), ALLOCATABLE :: zwater ! water cover
65 REAL, DIMENSION(:), ALLOCATABLE :: zland ! land cover
66 REAL, DIMENSION(:), ALLOCATABLE :: zfull ! total cover
67 !
68 INTEGER :: ilu ! total horizontal size
69 REAL(KIND=JPRB) :: zhook_handle
70 !-------------------------------------------------------------------------------
71 !
72 IF (lhook) CALL dr_hook('GET_TYPE_DIM_N',0,zhook_handle)
73 IF (.NOT. ASSOCIATED(u%XCOVER) .AND. lhook) CALL dr_hook('GET_TYPE_DIM_N',1,zhook_handle)
74 IF (.NOT. ASSOCIATED(u%XCOVER)) RETURN
75 !
76 !* 1. Fractions
77 ! ---------
78 !
79 ilu = SIZE(u%XCOVER,1)
80 !
81 ALLOCATE(zsea(ilu))
82 ALLOCATE(znature(ilu))
83 ALLOCATE(ztown(ilu))
84 ALLOCATE(zwater(ilu))
85 ALLOCATE(zland(ilu))
86 IF (.NOT. ASSOCIATED(u%XSEA)) THEN
87  CALL convert_cover_frac(dtco, &
88  u%XCOVER,u%LCOVER,zsea,znature,ztown,zwater)
89 ELSE
90  zsea = u%XSEA
91  znature = u%XNATURE
92  zwater = u%XWATER
93  ztown = u%XTOWN
94 END IF
95 zland = ztown + znature
96 !
97 ALLOCATE(zfull(ilu))
98 zfull=1.
99 !
100 SELECT CASE (htype)
101  CASE ('FULL ')
102  kdim = ilu
103  !
104  CASE ('EXTZON')
105  kdim = ilu
106  !
107  CASE ('NATURE')
108  kdim = count(znature(:) > 0.)
109  !
110  CASE ('SEA ')
111  kdim = count(zsea(:) > 0.)
112  !
113  CASE ('TOWN ')
114  kdim = count(ztown(:) > 0.)
115  !
116  CASE ('WATER ')
117  kdim = count(zwater(:) > 0.)
118  !
119  CASE ('LAND ')
120  kdim = count(zland(:) > 0.)
121  !
122 END SELECT
123 !-------------------------------------------------------------------------------
124 DEALLOCATE(zsea )
125 DEALLOCATE(znature)
126 DEALLOCATE(ztown )
127 DEALLOCATE(zwater )
128 DEALLOCATE(zfull )
129 DEALLOCATE(zland )
130 IF (lhook) CALL dr_hook('GET_TYPE_DIM_N',1,zhook_handle)
131 !-------------------------------------------------------------------------------
132 !
133 END SUBROUTINE get_type_dim_n
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine convert_cover_frac(DTCO, PCOVER, OCOVER, PSEA, PNATURE, PTOWN, PWATER)