SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
pack_pgd_seaflux.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_seaflux (DTCO, SG, S, U, &
7  hprogram,pseabathy)
8 ! ##############################################################
9 !
10 !!**** *PACK_PGD_SEAFLUX* packs SEAFLUX physiographic fields from all surface points to SEAFLUX points
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !! METHOD
16 !! ------
17 !!
18 !
19 !! EXTERNAL
20 !! --------
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !! AUTHOR
29 !! ------
30 !!
31 !! P. Le Moigne Meteo-France
32 !!
33 !! MODIFICATION
34 !! ------------
35 !!
36 !! Original 09/2007
37 !! Lebeaupin-B C. 01/2008 : include bathymetry
38 !!
39 !----------------------------------------------------------------------------
40 !
41 !* 0. DECLARATION
42 ! -----------
43 !
44 !
45 !
46 !
49 USE modd_seaflux_n, ONLY : seaflux_t
50 USE modd_surf_atm_n, ONLY : surf_atm_t
51 !
53 !
54 USE yomhook ,ONLY : lhook, dr_hook
55 USE parkind1 ,ONLY : jprb
56 !
57 USE modi_get_surf_mask_n
58 !
59 USE modi_get_type_dim_n
60 !
61 USE modi_get_luout
62 IMPLICIT NONE
63 !
64 !* 0.1 Declaration of arguments
65 ! ------------------------
66 !
67 !
68 TYPE(data_cover_t), INTENT(INOUT) :: dtco
69 TYPE(seaflux_grid_t), INTENT(INOUT) :: sg
70 TYPE(seaflux_t), INTENT(INOUT) :: s
71 TYPE(surf_atm_t), INTENT(INOUT) :: u
72 !
73  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
74 REAL, DIMENSION(:), INTENT(IN) :: pseabathy ! bathymetry
75 !
76 !* 0.2 Declaration of local variables
77 ! ------------------------------
78 !
79 INTEGER :: ilu ! expected physical size of full surface array
80 INTEGER :: iluout ! output listing logical unit
81 INTEGER, DIMENSION(:), POINTER :: imask ! mask for packing from complete field to nature field
82 REAL(KIND=JPRB) :: zhook_handle
83 !
84 !-------------------------------------------------------------------------------
85 !
86 IF (lhook) CALL dr_hook('PACK_PGD_SEAFLUX',0,zhook_handle)
87  CALL get_luout(hprogram,iluout)
88 !
89 !* 1. Number of points and packing
90 ! ----------------------------
91 !
92  CALL get_type_dim_n(dtco, u, &
93  'SEA ',sg%NDIM)
94 ALLOCATE(imask(sg%NDIM))
95 ilu=0
96  CALL get_surf_mask_n(dtco, u, &
97  'SEA ',sg%NDIM,imask,ilu,iluout)
98 !
99 !
100 !-------------------------------------------------------------------------------
101 !
102 !* 2. Packing of fields
103 ! -----------------
104 !
105 ALLOCATE(s%XSEABATHY(sg%NDIM))
106  CALL pack_same_rank(imask,pseabathy(:),s%XSEABATHY(:))
107 IF (lhook) CALL dr_hook('PACK_PGD_SEAFLUX',1,zhook_handle)
108 !
109 !-------------------------------------------------------------------------------
110 !
111 END SUBROUTINE pack_pgd_seaflux
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine get_surf_mask_n(DTCO, U, HTYPE, KDIM, KMASK, KLU, KLUOUT)
subroutine pack_pgd_seaflux(DTCO, SG, S, U, HPROGRAM, PSEABATHY)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6