SURFEX v8.1
General documentation of Surfex
hor_interpol.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 hor_interpol (DTCO, U, GCP, KLUOUT,PFIELDIN,PFIELDOUT)
7 ! #################################################################################
8 !
9 !!**** *HOR_INTERPOL * - Call the interpolation of a surface field
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !!
21 !! AUTHOR
22 !! ------
23 !! V. Masson
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 01/2004
28 !! P. Le Moigne 10/2005, Phasage Arome
29 !!------------------------------------------------------------------
30 !
32 USE modd_surf_atm_n, ONLY : surf_atm_t
34 !
36 !
37 USE modi_hor_interpol_gauss
38 USE modi_hor_interpol_rotlatlon
39 USE modi_hor_interpol_arome
40 USE modi_hor_interpol_conf_proj
41 USE modi_hor_interpol_cartesian
42 USE modi_hor_interpol_latlon
43 !
44 !
45 USE yomhook ,ONLY : lhook, dr_hook
46 USE parkind1 ,ONLY : jprb
47 !
48 USE modi_abor1_sfx
49 !
50 USE modi_hor_interpol_buffer
51 IMPLICIT NONE
52 !
53 !* 0.1 declarations of arguments
54 !
55 !
56 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
57 TYPE(surf_atm_t), INTENT(INOUT) :: U
58 TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
59 !
60 INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing
61 REAL, DIMENSION(:,:), INTENT(IN) :: PFIELDIN ! field to interpolate horizontally
62 REAL, DIMENSION(:,:), INTENT(OUT) :: PFIELDOUT ! interpolated field
63 !
64 !* 0.2 declarations of local variables
65 !
66 INTEGER :: JL ! loop counter
67 REAL(KIND=JPRB) :: ZHOOK_HANDLE
68 !
69 !-------------------------------------------------------------------------------------
70 !
71 IF (lhook) CALL dr_hook('HOR_INTERPOL',0,zhook_handle)
72 SELECT CASE (cinterp_type)
73 !
74 !* 1. Interpolation with horibl (from gaussian, Legendre or regular grid)
75 ! -------------------------------------------------------------------
76 !
77  CASE('HORIBL')
78  SELECT CASE(cingrid_type)
79 !
80 !* 1.1 Interpolation from gaussian or Legendre
81 !
82  CASE ('GAUSS ')
83  CALL hor_interpol_gauss(kluout,pfieldin,pfieldout)
84 !
85 !* 1.2 Interpolation from regular grid
86 !
87  CASE ('AROME ')
88  CALL hor_interpol_arome(kluout,pfieldin,pfieldout)
89 !
90 !* 1.3 Interpolation from regular lat/lon coord
91 !
92  CASE ('LATLON ')
93  CALL hor_interpol_latlon(kluout,pfieldin,pfieldout)
94 !
95 !* 1.4 Interpolation from rotated lat/lon coord
96 !
97  CASE ('ROTLATLON ')
98  CALL hor_interpol_rotlatlon(kluout,pfieldin,pfieldout)
99 
100  CASE DEFAULT
101  CALL abor1_sfx('HOR_INTERPOL: WRONG GRID TYPE'//cingrid_type)
102 
103  END SELECT
104 !
105 !* 2. Prescribed uniform field
106 ! ------------------------
107 !
108  CASE('UNIF ')
109  DO jl=1,SIZE(pfieldin,2)
110  pfieldout(:,jl) = pfieldin(1,jl)
111  END DO
112 !
113 !* 3. Bilinear interpolation
114 ! ----------------------
115 !
116  CASE('BILIN ')
117  SELECT CASE(cingrid_type)
118  CASE ('CONF PROJ ')
119  CALL hor_interpol_conf_proj(gcp,kluout,pfieldin,pfieldout)
120  CASE ('CARTESIAN ')
121  CALL hor_interpol_cartesian(kluout,pfieldin,pfieldout)
122  END SELECT
123 !
124 !* 4. no interpolation, only packing
125 ! ------------------------------
126 !
127  CASE('BUFFER')
128  CALL hor_interpol_buffer(dtco, u, kluout,pfieldin,pfieldout)
129 
130 !
131 !* 4. no interpolation
132 ! ----------------
133 !
134  CASE('NONE ')
135  DO jl=1,SIZE(pfieldin,2)
136  pfieldout(:,jl) = pfieldin(:,jl)
137  END DO
138 
139  CASE DEFAULT
140  CALL abor1_sfx('HOR_INTERPOL: WRONG INTERPOLATION TYPE'//cinterp_type)
141 
142 END SELECT
143 IF (lhook) CALL dr_hook('HOR_INTERPOL',1,zhook_handle)
144 !
145 !-------------------------------------------------------------------------------------
146 END SUBROUTINE hor_interpol
character(len=10) cingrid_type
Definition: modd_prep.F90:39
subroutine hor_interpol_conf_proj(GCP, KLUOUT, PFIELDIN, PFIELDOUT)
character(len=6) cinterp_type
Definition: modd_prep.F90:40
subroutine hor_interpol_gauss(KLUOUT, PFIELDIN, PFIELDOUT)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
subroutine hor_interpol(DTCO, U, GCP, KLUOUT, PFIELDIN, PFIELDOUT)
Definition: hor_interpol.F90:7
integer, parameter jprb
Definition: parkind1.F90:32
subroutine hor_interpol_cartesian(KLUOUT, PFIELDIN, PFIELDOUT)
subroutine hor_interpol_buffer(DTCO, U, KLUOUT, PFIELDIN, PFIELDOUT)
subroutine hor_interpol_arome(KLUOUT, PFIELDIN, PFIELDOUT)
subroutine hor_interpol_latlon(KLUOUT, PFIELDIN, PFIELDOUT)
logical lhook
Definition: yomhook.F90:15
subroutine hor_interpol_rotlatlon(KLUOUT, PFIELDIN, PFIELDOUT)