SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
prep_output_grid.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 prep_output_grid (UG, U, &
7  kluout,hgrid,pgrid_par,plat,plon)
8 ! #######################################
9 !!
10 !! PURPOSE
11 !! -------
12 !! Computes variables used for interpolation
13 !!
14 !! METHOD
15 !! ------
16 !!
17 !! EXTERNAL
18 !! --------
19 !!
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !! AUTHOR
29 !! ------
30 !!
31 !! V. Masson Meteo-France
32 !!
33 !! MODIFICATION
34 !! ------------
35 !!
36 !! Original 01/2004
37 !----------------------------------------------------------------------------
38 !
39 !* 0. DECLARATION
40 ! -----------
41 !
42 !
43 !
45 USE modd_surf_atm_n, ONLY : surf_atm_t
46 !
47 USE modi_get_grid_coord
48 !
49 USE modd_prep, ONLY : xlat_out, xlon_out, xx_out, xy_out, linterp
50 !
51 !
52 USE yomhook ,ONLY : lhook, dr_hook
53 USE parkind1 ,ONLY : jprb
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1 Declaration of dummy arguments
58 ! ------------------------------
59 !
60 !
61 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
62 TYPE(surf_atm_t), INTENT(INOUT) :: u
63 !
64 INTEGER, INTENT(IN) :: kluout ! output listing logical unit
65  CHARACTER(LEN=10), INTENT(IN) :: hgrid ! grid type
66 REAL, DIMENSION(:), POINTER :: pgrid_par ! parameters defining this grid
67 REAL, DIMENSION(:),INTENT(IN) :: plat ! latitudes
68 REAL, DIMENSION(:),INTENT(IN) :: plon ! longitudes
69 REAL(KIND=JPRB) :: zhook_handle
70 !
71 !
72 !* 0.2 Declaration of local variables
73 ! ------------------------------
74 !
75 !
76 !------------------------------------------------------------------------------
77 !
78 IF (lhook) CALL dr_hook('PREP_OUTPUT_GRID',0,zhook_handle)
79 IF (.NOT.ALLOCATED(xlat_out)) ALLOCATE(xlat_out(SIZE(plat)))
80 IF (.NOT.ALLOCATED(xlon_out)) ALLOCATE(xlon_out(SIZE(plat)))
81 IF (.NOT.ALLOCATED(xx_out)) ALLOCATE(xx_out(SIZE(plat)))
82 IF (.NOT.ALLOCATED(xy_out)) ALLOCATE(xy_out(SIZE(plat)))
83 !
84 IF (.NOT.ALLOCATED(linterp)) ALLOCATE(linterp(SIZE(plat)))
85 
86 xlat_out = plat
87 xlon_out = plon
88 linterp = .true.
89 !
90  CALL get_grid_coord(ug, u, &
91  kluout,xx_out,xy_out,SIZE(plat),hgrid,pgrid_par)
92 IF (lhook) CALL dr_hook('PREP_OUTPUT_GRID',1,zhook_handle)
93 !-------------------------------------------------------------------------------
94 !
95 END SUBROUTINE prep_output_grid
subroutine get_grid_coord(UG, U, KLUOUT, PX, PY, KL, HGRID, PGRID_PAR)
subroutine prep_output_grid(UG, U, KLUOUT, HGRID, PGRID_PAR, PLAT, PLON)