SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
interp_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 !######################
7 !######################
8 
9 INTERFACE interp_grid
10 
11 SUBROUTINE interp_grid_1d(PZ1,PT1,PZ2,PT2)
12 !
13 REAL, DIMENSION(:,:), INTENT(IN) :: pz1 ! input vertical grid
14 REAL, DIMENSION(:,:), INTENT(IN) :: pt1 ! input temperatures
15 REAL, DIMENSION(:), INTENT(IN) :: pz2 ! output vertical grid
16 REAL, DIMENSION(:,:), INTENT(OUT) :: pt2 ! output temperatures
17 !
18 END SUBROUTINE interp_grid_1d
19 !
20 SUBROUTINE interp_grid_2d(PZ1,PT1,PZ2,PT2)
21 !
22 REAL, DIMENSION(:,:), INTENT(IN) :: pz1 ! input vertical grid
23 REAL, DIMENSION(:,:), INTENT(IN) :: pt1 ! input temperatures
24 REAL, DIMENSION(:,:), INTENT(IN) :: pz2 ! output vertical grid
25 REAL, DIMENSION(:,:), INTENT(OUT) :: pt2 ! output temperatures
26 !
27 END SUBROUTINE interp_grid_2d
28 !
29 END INTERFACE
30 
31 END MODULE modi_interp_grid
32 
33 ! ##########################################
34  SUBROUTINE interp_grid_1d(PZ1,PT1,PZ2,PT2)
35 ! ##########################################
36 !!
37 !!**** *INTERP_GRID* - interpolation on the vertical
38 !!
39 !! PURPOSE
40 !! -------
41 !!
42 !! input grid/data is (x,z1)
43 !! output grid/data is (x,z2)
44 !!
45 !!** METHOD
46 !! ------
47 !!
48 !! REFERENCE
49 !! ---------
50 !!
51 !!
52 !! AUTHOR
53 !! ------
54 !! V. Masson
55 !!
56 !! MODIFICATIONS
57 !! -------------
58 !! Original 01/2004
59 !!------------------------------------------------------------------
60 !
61 USE modd_surf_par, ONLY : xundef
62 USE modi_coef_ver_interp_lin_surf
64 !
65 USE yomhook ,ONLY : lhook, dr_hook
66 USE parkind1 ,ONLY : jprb
67 !
68 IMPLICIT NONE
69 !
70 !* 0.1 Declaration of dummy arguments
71 !
72 REAL, DIMENSION(:,:), INTENT(IN) :: pz1 ! input vertical grid
73 REAL, DIMENSION(:,:), INTENT(IN) :: pt1 ! input temperatures
74 REAL, DIMENSION(:), INTENT(IN) :: pz2 ! output vertical grid
75 REAL, DIMENSION(:,:), INTENT(OUT) :: pt2 ! output temperatures
76 !
77 !* 0.2 Declaration of local variables
78 !
79 INTEGER :: jl, ji ! loop counter
80 REAL, DIMENSION(SIZE(PZ1,1),SIZE(PZ2)) :: zz2 ! output grid
81 REAL, DIMENSION(SIZE(PZ1,1),SIZE(PZ2)) :: zcoeflin ! interpolation coefficients
82 INTEGER, DIMENSION(SIZE(PZ1,1),SIZE(PZ2)) :: iklin ! lower interpolating level of
83 ! ! grid 1 for each level of grid 2
84 REAL(KIND=JPRB) :: zhook_handle
85 !-----------------------------------------------------------------------------
86 IF (lhook) CALL dr_hook('MODI_INTERP_GRID:INTERP_GRID_1D',0,zhook_handle)
87 DO jl=1,SIZE(pz2)
88  zz2(:,jl) = pz2(jl)
89 END DO
90 !
91  CALL coef_ver_interp_lin_surf(pz1,zz2,kklin=iklin,pcoeflin=zcoeflin)
92 !
93 !
94 pt2= ver_interp_lin_surf(pt1,iklin,zcoeflin)
95 !
96 ! On reporte le mask sur tous les niveaux
97 !
98 DO jl=1,SIZE(pt1,2)
99  DO ji=1,SIZE(pt1,1)
100  IF (pt1(ji,jl)==xundef) THEN
101  pt2(ji,:)=xundef
102  ENDIF
103  END DO
104 END DO
105 IF (lhook) CALL dr_hook('MODI_INTERP_GRID:INTERP_GRID_1D',1,zhook_handle)
106 !-----------------------------------------------------------------------------
107 END SUBROUTINE interp_grid_1d
108 !
109 ! ##########################################
110  SUBROUTINE interp_grid_2d(PZ1,PT1,PZ2,PT2)
111 ! ##########################################
112 !
113 USE modd_surf_par, ONLY : xundef
114 USE modi_coef_ver_interp_lin_surf
116 !
117 USE yomhook ,ONLY : lhook, dr_hook
118 USE parkind1 ,ONLY : jprb
119 !
120 IMPLICIT NONE
121 !
122 !* 0.1 Declaration of dummy arguments
123 !
124 REAL, DIMENSION(:,:), INTENT(IN) :: pz1 ! input vertical grid
125 REAL, DIMENSION(:,:), INTENT(IN) :: pt1 ! input temperatures
126 REAL, DIMENSION(:,:), INTENT(IN) :: pz2 ! output vertical grid
127 REAL, DIMENSION(:,:), INTENT(OUT) :: pt2 ! output temperatures
128 !
129 !* 0.2 Declaration of local variables
130 !
131 INTEGER :: jl, ji ! loop counter
132 REAL, DIMENSION(SIZE(PZ1,1),SIZE(PZ2,2)) :: zcoeflin ! interpolation coefficients
133 INTEGER, DIMENSION(SIZE(PZ1,1),SIZE(PZ2,2)) :: iklin ! lower interpolating level of
134  ! grid 1 for each level of grid 2
135 REAL(KIND=JPRB) :: zhook_handle
136 !-----------------------------------------------------------------------------
137 IF (lhook) CALL dr_hook('MODI_INTERP_GRID:INTERP_GRID_2D',0,zhook_handle)
138  CALL coef_ver_interp_lin_surf(pz1,pz2,iklin,zcoeflin)
139 !
140 pt2= ver_interp_lin_surf(pt1,iklin,zcoeflin)
141 !
142 ! On reporte le mask sur tous les niveaux
143 !
144 DO jl=1,SIZE(pt1,2)
145  DO ji=1,SIZE(pt1,1)
146  IF (pt1(ji,jl)==xundef) THEN
147  pt2(ji,:)=xundef
148  ENDIF
149  END DO
150 END DO
151 IF (lhook) CALL dr_hook('MODI_INTERP_GRID:INTERP_GRID_2D',1,zhook_handle)
152 !-----------------------------------------------------------------------------
153 END SUBROUTINE interp_grid_2d
subroutine interp_grid_2d(PZ1, PT1, PZ2, PT2)
subroutine interp_grid_1d(PZ1, PT1, PZ2, PT2)
Definition: interp_grid.F90:34
subroutine coef_ver_interp_lin_surf(PZ1, PZ2, KKLIN, PCOEFLIN)