SURFEX v8.1
General documentation of Surfex
pack_pgd.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 pack_pgd (DTCO, U, HPROGRAM, HSURF, G, OCOVER, PCOVER, PZS, PDIR )
7 ! ##############################################################
8 !
9 !!**** *PACK_PGD* packs ISBA physiographic fields from all surface points to ISBA points
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! METHOD
15 !! ------
16 !!
17 !
18 !! EXTERNAL
19 !! --------
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !! AUTHOR
28 !! ------
29 !!
30 !! V. Masson Meteo-France
31 !!
32 !! MODIFICATION
33 !! ------------
34 !!
35 !! Original 03/2004
36 !! Escobar J. 08/02/2005 : bug declare ILU local variable
37 !!
38 !----------------------------------------------------------------------------
39 !
40 !* 0. DECLARATION
41 ! -----------
42 !
43 !
44 USE modd_sfx_grid_n, ONLY : grid_t
45 !
47 USE modd_surf_atm_n, ONLY : surf_atm_t
48 !
49 USE modd_pgd_grid, ONLY : nl, cgrid, xgrid_par
50 !
51 USE modd_data_cover_par, ONLY : jpcover
52 !
53 USE modi_get_cover_n
54 USE modi_get_lcover_n
55 USE modi_get_zs_n
57 USE modi_pack_grid
58 USE modi_latlon_grid
59 !
60 USE yomhook ,ONLY : lhook, dr_hook
61 USE parkind1 ,ONLY : jprb
62 !
63 USE modi_get_surf_mask_n
64 !
65 USE modi_get_type_dim_n
66 !
67 USE modi_get_luout
68 IMPLICIT NONE
69 !
70 !* 0.1 Declaration of arguments
71 ! ------------------------
72 !
73 !
74 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
75 TYPE(surf_atm_t), INTENT(INOUT) :: U
76 TYPE(grid_t), INTENT(INOUT) :: G
77 !
78  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! Type of program
79  CHARACTER(LEN=6), INTENT(IN) :: HSURF ! surface type
80 !
81 LOGICAL, DIMENSION(:), INTENT(OUT):: OCOVER ! list of present cover
82 REAL, DIMENSION(:,:), POINTER :: PCOVER ! cover fraction
83 REAL, DIMENSION(:), INTENT(OUT):: PZS ! zs
84 REAL, DIMENSION(:), INTENT(OUT), OPTIONAL :: PDIR ! angle of grid axis with N.
85 !
86 !
87 !* 0.2 Declaration of local variables
88 ! ------------------------------
89 !
90 INTEGER :: ILUOUT ! output listing logical unit
91 INTEGER :: IL ! number of points
92 INTEGER :: ILU ! expected physical size of full surface array
93 INTEGER :: JCOVER
94 INTEGER, DIMENSION(:), POINTER :: IMASK ! mask for packing from complete field to nature field
95 REAL, DIMENSION(SIZE(G%XLAT)) :: ZDIR
96 !
97 REAL, DIMENSION(NL) :: ZCOVER ! cover on all surface points
98 REAL, DIMENSION(NL) :: ZZS ! zs on all surface points
99 REAL(KIND=JPRB) :: ZHOOK_HANDLE
100 !-------------------------------------------------------------------------------
101 !
102 IF (lhook) CALL dr_hook('PACK_PGD',0,zhook_handle)
103  CALL get_luout(hprogram,iluout)
104 !
105 !* 1. Number of points and packing
106 ! ----------------------------
107 !
108  CALL get_type_dim_n(dtco, u, hsurf,il)
109 !
110 ALLOCATE(imask(il))
111 ilu=0
112  CALL get_surf_mask_n(dtco, u, hsurf,il,imask,ilu,iluout)
113 !
114 !-------------------------------------------------------------------------------
115 !
116 !* 2. Packing of grid
117 ! ---------------
118 !
119  CALL pack_grid(imask,cgrid,g%CGRID,xgrid_par,g%XGRID_PAR)
120 !
121  CALL get_lcover_n(u,hprogram,jpcover,ocover)
122 !
123 IF (il==0) THEN
124  ALLOCATE(pcover(0,0))
125  IF (lhook) CALL dr_hook('PACK_PGD',1,zhook_handle)
126  RETURN
127 ENDIF
128 !
129 !-------------------------------------------------------------------------------
130 !
131 !* 3. Computes geographical quantities
132 ! --------------------------------
133 !
134  CALL latlon_grid(g,il,zdir)
135 !
136 IF (PRESENT(pdir)) pdir = zdir
137 !
138 !-------------------------------------------------------------------------------
139 !
140 !* 4. Packing of fields
141 ! -----------------
142 !
143 IF (hsurf=='NATURE') THEN
144  !
145  ALLOCATE(pcover(SIZE(g%XLAT),count(ocover)))
146  !
147  DO jcover=1,count(ocover)
148  CALL get_cover_n(u,hprogram,jcover,zcover)
149  CALL pack_same_rank(imask,zcover(:),pcover(:,jcover))
150  ENDDO
151  !
152 ELSE
153  !
154  ALLOCATE(pcover(0,0))
155  !
156 ENDIF
157 !
158  CALL get_zs_n(u, hprogram,nl,zzs)
159 !
160 !
161 !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
162 !
163  CALL pack_same_rank(imask,zzs(:),pzs(:))
164 !
165 !-------------------------------------------------------------------------------
166 !
167 DEALLOCATE(imask)
168 !
169 IF (lhook) CALL dr_hook('PACK_PGD',1,zhook_handle)
170 !
171 !-------------------------------------------------------------------------------
172 !
173 END SUBROUTINE pack_pgd
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine latlon_grid(G, KL, PDIR)
Definition: latlon_grid.F90:7
subroutine pack_pgd(DTCO, U, HPROGRAM, HSURF, G, OCOVER, PCOVER,
Definition: pack_pgd.F90:7
subroutine get_surf_mask_n(DTCO, U, HTYPE, KDIM, KMASK, KLU, KLUOUT)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine get_lcover_n(U, HPROGRAM, KCOVER, OCOVER)
Definition: get_lcovern.F90:7
real, dimension(:), pointer xgrid_par
subroutine get_cover_n(U, HPROGRAM, KCOVER, PCOVER)
Definition: get_covern.F90:8
subroutine pack_grid(KMASK, HGRID1, HGRID2, PGRID_PAR1, PGRID_PAR2)
Definition: pack_grid.F90:7
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
logical lhook
Definition: yomhook.F90:15
subroutine get_zs_n(U, HPROGRAM, KI, PZS)
Definition: get_zsn.F90:8
character(len=10) cgrid
static int count
Definition: memory_hook.c:21