source: lmdz_wrf/WRFV3/share/mediation_interp_domain.F @ 1

Last change on this file since 1 was 1, checked in by lfita, 10 years ago
  • -- --- Opening of the WRF+LMDZ coupling repository --- -- -

WRF: version v3.3
LMDZ: version v1818

More details in:

File size: 9.3 KB
Line 
1!
2!WRF:MEDIATION_LAYER:NESTING
3!
4SUBROUTINE med_interp_domain ( parent_grid , nested_grid )
5   USE module_domain
6   USE module_configure
7   USE module_timing
8   IMPLICIT NONE
9   TYPE(domain), POINTER :: parent_grid , nested_grid
10   TYPE(domain), POINTER :: grid
11   INTEGER nlev, msize
12   TYPE (grid_config_rec_type)            :: config_flags
13
14! ----------------------------------------------------------
15! ----------------------------------------------------------
16! Interface blocks
17! ----------------------------------------------------------
18   INTERFACE
19! ----------------------------------------------------------
20!    Interface definitions for EM CORE
21! ----------------------------------------------------------
22#if (EM_CORE == 1)
23! ----------------------------------------------------------
24!    These routines are supplied by module_dm.F from the
25!    external communication package (e.g. external/RSL)
26! ----------------------------------------------------------
27      SUBROUTINE interp_domain_em_part1 ( grid, intermediate_grid, ngrid, config_flags   &
28!
29#        include "dummy_new_args.inc"
30!
31                 )
32         USE module_domain
33         USE module_configure
34         TYPE(domain), POINTER :: grid          ! name of the grid being dereferenced (must be "grid")
35         TYPE(domain), POINTER :: intermediate_grid
36         TYPE(domain), POINTER :: ngrid
37         TYPE (grid_config_rec_type)            :: config_flags
38#        include <dummy_new_decl.inc>
39      END SUBROUTINE interp_domain_em_part1
40
41      SUBROUTINE interp_domain_em_part2 ( grid, nested_grid, config_flags   &
42!
43#        include "dummy_new_args.inc"
44!
45                 )
46         USE module_domain
47         USE module_configure
48         TYPE(domain), POINTER :: grid          ! name of the grid being dereferenced (must be "grid")
49         TYPE(domain), POINTER :: nested_grid
50         TYPE (grid_config_rec_type)            :: config_flags
51#        include <dummy_new_decl.inc>
52      END SUBROUTINE interp_domain_em_part2
53#endif
54! ----------------------------------------------------------
55!    Interface definitions for NMM (placeholder)
56! ----------------------------------------------------------
57#if (NMM_CORE == 1 && NMM_NEST == 1)
58!=======================================================================
59!  Added for the NMM core. This is gopal's doing.
60!=======================================================================
61
62      SUBROUTINE interp_domain_nmm_part1 ( grid, intermediate_grid, ngrid, config_flags    &
63!
64# include "dummy_new_args.inc"
65!
66                 )
67         USE module_domain
68         USE module_configure
69         TYPE(domain), POINTER :: grid          ! name of the grid being dereferenced (must be "grid")
70         TYPE(domain), POINTER :: intermediate_grid
71         TYPE(domain), POINTER :: ngrid
72         TYPE (grid_config_rec_type)            :: config_flags
73# include <dummy_new_decl.inc>
74      END SUBROUTINE interp_domain_nmm_part1
75
76      SUBROUTINE interp_domain_nmm_part2 ( grid, nested_grid, config_flags    &
77!
78# include "dummy_new_args.inc"
79!
80                 )
81         USE module_domain
82         USE module_configure
83         TYPE(domain), POINTER :: grid          ! name of the grid being dereferenced (must be "grid")
84         TYPE(domain), POINTER :: nested_grid
85         TYPE (grid_config_rec_type)            :: config_flags
86# include <dummy_new_decl.inc>
87      END SUBROUTINE interp_domain_nmm_part2
88
89!=======================================================================
90!  End of gopal's doing.
91!=======================================================================
92#endif
93! ----------------------------------------------------------
94!    Interface definitions for COAMPS (placeholder)
95! ----------------------------------------------------------
96#if (COAMPS_CORE == 1)
97#endif
98   END INTERFACE
99! ----------------------------------------------------------
100! End of Interface blocks
101! ----------------------------------------------------------
102! ----------------------------------------------------------
103! ----------------------------------------------------------
104! Executable code
105! ----------------------------------------------------------
106! ----------------------------------------------------------
107!    Interpolation calls for EM CORE.  The called
108!    routines below are supplied by module_dm.F
109!    from the external communications package (e.g. RSL)
110! ----------------------------------------------------------
111#if (EM_CORE == 1 && defined( DM_PARALLEL ))
112  CALL model_to_grid_config_rec ( nested_grid%id , model_config_rec , config_flags )
113  grid => nested_grid%intermediate_grid
114# if defined(MOVE_NESTS) || (!defined(SGIALTIX))
115
116  CALL alloc_space_field ( grid, grid%id , 1 , 2 , .TRUE. ,   &
117                           grid%sd31, grid%ed31, grid%sd32, grid%ed32, grid%sd33, grid%ed33, &
118                           grid%sm31,  grid%em31,  grid%sm32,  grid%em32,  grid%sm33,  grid%em33, &
119                           grid%sp31,  grid%ep31,  grid%sp32,  grid%ep32,  grid%sp33,  grid%ep33, &
120                           grid%sp31x, grid%ep31x, grid%sp32x, grid%ep32x, grid%sp33x, grid%ep33x,&
121                           grid%sp31y, grid%ep31y, grid%sp32y, grid%ep32y, grid%sp33y, grid%ep33y,&
122                           grid%sm31x, grid%em31x, grid%sm32x, grid%em32x, grid%sm33x, grid%em33x, &   ! x-xpose
123                           grid%sm31y, grid%em31y, grid%sm32y, grid%em32y, grid%sm33y, grid%em33y  &   ! y-xpose
124    )
125# endif
126
127  grid => parent_grid
128
129  CALL model_to_grid_config_rec ( grid%id , model_config_rec , config_flags )
130  CALL interp_domain_em_part1 ( grid , nested_grid%intermediate_grid, nested_grid, config_flags   &
131!
132#     include "actual_new_args.inc"
133!
134                                )
135  grid => nested_grid%intermediate_grid
136  CALL model_to_grid_config_rec ( grid%id , model_config_rec , config_flags )
137  CALL interp_domain_em_part2 ( grid, nested_grid, config_flags   &
138!
139#     include "actual_new_args.inc"
140!
141                                )
142
143  grid => nested_grid%intermediate_grid
144  CALL model_to_grid_config_rec ( grid%id , model_config_rec , config_flags )
145# if defined(MOVE_NESTS) || (!defined(SGIALTIX))
146  CALL dealloc_space_field ( grid )
147# endif
148#endif
149! ------------------------------------------------------
150!    End of Interpolation calls for EM CORE.
151! ------------------------------------------------------
152! ------------------------------------------------------
153! ------------------------------------------------------
154!    Interpolation calls for NMM. (Placeholder)
155! ------------------------------------------------------
156#if (NMM_CORE == 1 && NMM_NEST == 1)
157!=======================================================================
158!  Added for the NMM core. This is gopal's doing.
159!=======================================================================
160!
161  CALL model_to_grid_config_rec ( nested_grid%id , model_config_rec , config_flags )
162  grid => nested_grid%intermediate_grid
163#if defined(MOVE_NESTS) || (!defined(SGIALTIX))
164#   if defined(HWRF)
165  CALL ensure_space_field &
166#   else
167  CALL alloc_space_field &
168#   endif
169                         ( grid, grid%id , 1 , 2 , .TRUE. ,   &
170                           grid%sd31, grid%ed31, grid%sd32, grid%ed32, grid%sd33, grid%ed33, &
171                           grid%sm31,  grid%em31,  grid%sm32,  grid%em32,  grid%sm33,  grid%em33, &
172                           grid%sp31,  grid%ep31,  grid%sp32,  grid%ep32,  grid%sp33,  grid%ep33, &
173                           grid%sp31x, grid%ep31x, grid%sp32x, grid%ep32x, grid%sp33x, grid%ep33x,&
174                           grid%sp31y, grid%ep31y, grid%sp32y, grid%ep32y, grid%sp33y, grid%ep33y,&
175                           grid%sm31x, grid%em31x, grid%sm32x, grid%em32x, grid%sm33x, grid%em33x, &   ! x-xpose
176                           grid%sm31y, grid%em31y, grid%sm32y, grid%em32y, grid%sm33y, grid%em33y  &   ! y-xpose
177      )
178#endif
179
180  grid => parent_grid
181
182  CALL model_to_grid_config_rec ( grid%id , model_config_rec , config_flags )
183
184  CALL interp_domain_nmm_part1 ( grid , nested_grid%intermediate_grid, nested_grid, config_flags    &
185!
186#     include "actual_new_args.inc"
187!
188                                )
189  grid => nested_grid%intermediate_grid
190  CALL model_to_grid_config_rec ( grid%id , model_config_rec , config_flags )
191
192  CALL interp_domain_nmm_part2 ( grid, nested_grid, config_flags    &
193!
194#     include "actual_new_args.inc"
195!
196                                )
197
198  grid => nested_grid%intermediate_grid
199  CALL model_to_grid_config_rec ( grid%id , model_config_rec , config_flags )
200#if defined(MOVE_NESTS) || (!defined(SGIALTIX))
201#   if !defined(HWRF)
202  CALL dealloc_space_field ( grid )
203#   endif
204#endif
205
206! ------------------------------------------------------------
207!    End of gopal's doing
208! ------------------------------------------------------------
209#endif
210! ------------------------------------------------------
211!    End of Interpolation calls for NMM.
212! ------------------------------------------------------
213! ------------------------------------------------------
214! ------------------------------------------------------
215!    Interpolation calls for COAMPS. (Placeholder)
216! ------------------------------------------------------
217#if (COAMPS_CORE == 1)
218#endif
219! ------------------------------------------------------
220!    End of Interpolation calls for COAMPS.
221! ------------------------------------------------------
222   RETURN
223END SUBROUTINE med_interp_domain
224
225
Note: See TracBrowser for help on using the repository browser.