SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
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 pgd_seaflux (DTCO, DTS, SG, S, UG, U, USS, &
7  hprogram)
8 ! ##############################################################
9 !
10 !!**** *PGD_SEAFLUX* monitor for averaging and interpolations of SEAFLUX physiographic fields
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 !! V. Masson Meteo-France
32 !!
33 !! MODIFICATION
34 !! ------------
35 !!
36 !! Original 03/2004
37 !! Lebeaupin-B C. 01/2008 : include bathymetry
38 !!
39 !----------------------------------------------------------------------------
40 !
41 !* 0. DECLARATION
42 ! -----------
43 !
44 !
45 !
46 !
50 USE modd_seaflux_n, ONLY : seaflux_t
52 USE modd_surf_atm_n, ONLY : surf_atm_t
54 !
55 USE modd_pgd_grid, ONLY : nl
56 USE modd_data_cover_par, ONLY : jpcover
57 !
58 USE modi_read_nam_pgd_seabathy
59 USE modi_pgd_bathyfield
60 !
61 USE modi_get_surf_size_n
62 USE modi_pack_pgd
63 USE modi_pack_pgd_seaflux
64 USE modi_pgd_seaflux_par
65 !
66 !
67 USE yomhook ,ONLY : lhook, dr_hook
68 USE parkind1 ,ONLY : jprb
69 !
70 IMPLICIT NONE
71 !
72 !* 0.1 Declaration of arguments
73 ! ------------------------
74 !
75 !
76 TYPE(data_cover_t), INTENT(INOUT) :: dtco
77 TYPE(data_seaflux_t), INTENT(INOUT) :: dts
78 TYPE(seaflux_grid_t), INTENT(INOUT) :: sg
79 TYPE(seaflux_t), INTENT(INOUT) :: s
80 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
81 TYPE(surf_atm_t), INTENT(INOUT) :: u
82 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
83 !
84  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
85 !
86 !
87 !* 0.2 Declaration of local variables
88 ! ------------------------------
89 !
90 REAL, DIMENSION(NL) :: zseabathy ! bathymetry on all surface points
91 !
92 !* 0.3 Declaration of namelists
93 ! ------------------------
94 !
95  CHARACTER(LEN=28) :: yseabathy ! file name for bathymetrie
96  CHARACTER(LEN=6) :: yseabathyfiletype ! bathymetry data file type
97  CHARACTER(LEN=28) :: yncvarname ! variable to read in netcdf
98  ! file
99 REAL :: xunif_seabathy ! uniform value of bathymetry
100 REAL(KIND=JPRB) :: zhook_handle
101 !
102 !
103 !-------------------------------------------------------------------------------
104 !
105 !* 1. Initializations of defaults
106 ! ---------------------------
107 !
108 !-------------------------------------------------------------------------------
109 !
110 !* 2. Reading of namelist
111 ! -------------------
112 !
113 IF (lhook) CALL dr_hook('PGD_SEAFLUX',0,zhook_handle)
114  CALL read_nam_pgd_seabathy(hprogram,yseabathy,yseabathyfiletype,yncvarname,&
115  xunif_seabathy)
116 !
117 !-------------------------------------------------------------------------------
118 !
119 !* 3. Coherence of options
120 ! --------------------
121 !
122 !-------------------------------------------------------------------------------
123 !
124 !* 4. Bathymetry
125 ! ----------
126 !
127  CALL pgd_bathyfield(ug, u, uss, &
128  hprogram,'bathymetry','SEA',yseabathy,yseabathyfiletype,&
129  yncvarname,xunif_seabathy,zseabathy(:))
130 !-------------------------------------------------------------------------------
131 !
132 !* 5. Number of points and packing
133 ! ----------------------------
134 !
135  CALL get_surf_size_n(dtco, u, &
136  'SEA ',sg%NDIM)
137 !
138 ALLOCATE(s%LCOVER (jpcover))
139 ALLOCATE(s%XZS (sg%NDIM))
140 ALLOCATE(sg%XLAT (sg%NDIM))
141 ALLOCATE(sg%XLON (sg%NDIM))
142 ALLOCATE(sg%XMESH_SIZE (sg%NDIM))
143 !
144  CALL pack_pgd(dtco, u, &
145  hprogram, 'SEA ', &
146  sg%CGRID, sg%XGRID_PAR, &
147  s%LCOVER, s%XCOVER, s%XZS, &
148  sg%XLAT, sg%XLON, sg%XMESH_SIZE )
149 !
150  CALL pack_pgd_seaflux(dtco, sg, s, u, &
151  hprogram, zseabathy)
152 !
153  CALL pgd_seaflux_par(dtco, dts, sg, ug, u, uss, &
154  hprogram,dts%LSST_DATA)
155 IF (lhook) CALL dr_hook('PGD_SEAFLUX',1,zhook_handle)
156 !-------------------------------------------------------------------------------
157 !
158 END SUBROUTINE pgd_seaflux
subroutine pgd_seaflux_par(DTCO, DTS, SG, UG, U, USS, HPROGRAM, OSST_DATA)
subroutine get_surf_size_n(DTCO, U, HTYPE, KL)
subroutine pack_pgd(DTCO, U, HPROGRAM, HSURF, HGRID, PGRID_PAR, OCOVER, PCOVER, PZS, PLAT, PLON, PMESH_SIZE, PDIR)
Definition: pack_pgd.F90:6
subroutine pack_pgd_seaflux(DTCO, SG, S, U, HPROGRAM, PSEABATHY)
subroutine pgd_seaflux(DTCO, DTS, SG, S, UG, U, USS, HPROGRAM)
Definition: pgd_seaflux.F90:6
subroutine pgd_bathyfield(UG, U, USS, HPROGRAM, HFIELD, HAREA, HFILE, HFILETYPE, HNCVARNAME, PUNIF, PFIELD)
subroutine read_nam_pgd_seabathy(HPROGRAM, HSEABATHY, HSEABATHYFILETYPE, HNCVARNAME, PUNIF_SEABATHY)