source: palm/trunk/SOURCE/nudging_mod.f90 @ 2272

Last change on this file since 2272 was 2271, checked in by sward, 7 years ago

error messages and numbers updated

  • Property svn:keywords set to Id
File size: 21.5 KB
Line 
1!> @file nudging_mod.f90
2!------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2017 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: nudging_mod.f90 2271 2017-06-09 12:34:55Z witha $
27! Error message changed
28!
29! 2233 2017-05-30 18:08:54Z suehring
30!
31! 2232 2017-05-30 17:47:52Z suehring
32! Adjustments to new topography concept
33!
34! 2000 2016-08-20 18:09:15Z knoop
35! Forced header and separation lines into 80 columns
36!
37! 1850 2016-04-08 13:29:27Z maronga
38! Module renamed
39!
40!
41! 1757 2016-02-22 15:49:32Z maronga
42! Bugfix: allow for using higher vertical resolution in nudging file than grid
43! spacing in the LES model
44!
45! 1682 2015-10-07 23:56:08Z knoop
46! Code annotations made doxygen readable
47!
48! 1398 2014-05-07 11:15:00Z heinze
49! Subroutine nudge_ref is extended to set u_init and v_init to the current
50! nudging profiles
51!
52! 1382 2014-04-30 12:15:41Z boeske
53! Changed the weighting factor that is used in the summation of nudging
54! tendencies for profile data output from weight_pres to weight_substep,
55! added Neumann boundary conditions for profile data output of nudging terms at
56! nzt+1
57!
58! 1380 2014-04-28 12:40:45Z heinze
59! Subroutine nudge_ref added to account for proper upper scalar boundary
60! conditions in case of nudging
61!
62! 1365 2014-04-22 15:03:56Z boeske
63! Variable t renamed nt, variable currtnudge renamed tmp_tnudge,
64! summation of nudging tendencies for data output added
65! +sums_ls_l, tmp_tend
66! Added new subroutine calc_tnudge, which calculates the current nudging time
67! scale at each time step
68!
69! 1355 2014-04-10 10:21:29Z heinze
70! Error message specified.
71!
72! 1353 2014-04-08 15:21:23Z heinze
73! REAL constants provided with KIND-attribute
74!
75! 1320 2014-03-20 08:40:49Z raasch
76! ONLY-attribute added to USE-statements,
77! kind-parameters added to all INTEGER and REAL declaration statements,
78! kinds are defined in new module kinds,
79! old module precision_kind is removed,
80! revision history before 2012 removed,
81! comment fields (!:) to be used for variable explanations added to
82! all variable declaration statements
83!
84! 1318 2014-03-17 13:35:16Z raasch
85! module interfaces removed
86!
87! 1268 2013-12-12 09:47:53Z heinze
88! bugfix: argument of calc_mean_profile corrected
89!
90! 1251 2013-11-07 08:14:30Z heinze
91! bugfix: calculate dtm and dtp also in vector version
92!
93! 1249 2013-11-06 10:45:47Z heinze
94! remove call of user module
95! reformatting
96!
97! 1241 2013-10-30 11:36:58Z heinze
98! Initial revision
99!
100! Description:
101! ------------
102!> Nudges u, v, pt and q to given profiles on a relaxation timescale tnudge.
103!> Profiles are read in from NUDGIN_DATA. Code is based on Neggers et al. (2012)
104!> and also part of DALES and UCLA-LES.
105!--------------------------------------------------------------------------------!
106 MODULE nudge_mod
107 
108
109    PRIVATE
110    PUBLIC init_nudge, calc_tnudge, nudge, nudge_ref
111    SAVE
112
113    INTERFACE nudge
114       MODULE PROCEDURE nudge
115       MODULE PROCEDURE nudge_ij
116    END INTERFACE nudge
117
118 CONTAINS
119
120!------------------------------------------------------------------------------!
121! Description:
122! ------------
123!> @todo Missing subroutine description.
124!------------------------------------------------------------------------------!
125    SUBROUTINE init_nudge
126
127       USE arrays_3d,                                                          &
128           ONLY:  ptnudge, qnudge, timenudge, tmp_tnudge, tnudge, unudge,      &
129                  vnudge, wnudge, zu
130
131       USE control_parameters,                                                 &
132           ONLY:  dt_3d, lptnudge, lqnudge, lunudge, lvnudge, lwnudge,         &
133                   message_string, ntnudge
134
135       USE indices,                                                            &
136           ONLY:  nzb, nzt
137
138       USE kinds
139
140       IMPLICIT NONE
141
142
143       INTEGER(iwp) ::  finput = 90  !<
144       INTEGER(iwp) ::  ierrn        !<
145       INTEGER(iwp) ::  k            !<
146       INTEGER(iwp) ::  nt            !<
147
148       CHARACTER(1) ::  hash     !<
149
150       REAL(wp) ::  highheight   !<
151       REAL(wp) ::  highqnudge   !<
152       REAL(wp) ::  highptnudge  !<
153       REAL(wp) ::  highunudge   !<
154       REAL(wp) ::  highvnudge   !<
155       REAL(wp) ::  highwnudge   !<
156       REAL(wp) ::  hightnudge   !<
157
158       REAL(wp) ::  lowheight    !<
159       REAL(wp) ::  lowqnudge    !<
160       REAL(wp) ::  lowptnudge   !<
161       REAL(wp) ::  lowunudge    !<
162       REAL(wp) ::  lowvnudge    !<
163       REAL(wp) ::  lowwnudge    !<
164       REAL(wp) ::  lowtnudge    !<
165
166       REAL(wp) ::  fac          !<
167
168       ALLOCATE( ptnudge(nzb:nzt+1,1:ntnudge), qnudge(nzb:nzt+1,1:ntnudge), &
169                 tnudge(nzb:nzt+1,1:ntnudge), unudge(nzb:nzt+1,1:ntnudge),  &
170                 vnudge(nzb:nzt+1,1:ntnudge), wnudge(nzb:nzt+1,1:ntnudge)  )
171
172       ALLOCATE( tmp_tnudge(nzb:nzt) )
173
174       ALLOCATE( timenudge(0:ntnudge) )
175
176       ptnudge = 0.0_wp; qnudge = 0.0_wp; tnudge = 0.0_wp; unudge = 0.0_wp
177       vnudge = 0.0_wp; wnudge = 0.0_wp; timenudge = 0.0_wp
178!
179!--    Initialize array tmp_nudge with a current nudging time scale of 6 hours
180       tmp_tnudge = 21600.0_wp
181
182       nt = 0
183       OPEN ( finput, FILE='NUDGING_DATA', STATUS='OLD', &
184              FORM='FORMATTED', IOSTAT=ierrn )
185
186       IF ( ierrn /= 0 )  THEN
187          message_string = 'file NUDGING_DATA does not exist'
188          CALL message( 'nudging', 'PA0365', 1, 2, 0, 6, 0 )
189       ENDIF
190
191       ierrn = 0
192
193 rloop:DO
194          nt = nt + 1
195          hash = "#"
196          ierrn = 1 ! not zero
197!
198!--       Search for the next line consisting of "# time",
199!--       from there onwards the profiles will be read
200          DO WHILE ( .NOT. ( hash == "#" .AND. ierrn == 0 ) ) 
201         
202            READ ( finput, *, IOSTAT=ierrn ) hash, timenudge(nt)
203            IF ( ierrn < 0 )  EXIT rloop
204
205          ENDDO
206
207          ierrn = 0
208          READ ( finput, *, IOSTAT=ierrn ) lowheight, lowtnudge, lowunudge,   &
209                                           lowvnudge, lowwnudge , lowptnudge, &
210                                           lowqnudge
211
212          IF ( ierrn /= 0 )  THEN
213             message_string = 'errors in file NUDGING_DATA'
214             CALL message( 'nudging', 'PA0366', 1, 2, 0, 6, 0 )
215          ENDIF
216
217          ierrn = 0
218          READ ( finput, *, IOSTAT=ierrn ) highheight, hightnudge, highunudge,   &
219                                           highvnudge, highwnudge , highptnudge, &
220                                           highqnudge
221
222          IF ( ierrn /= 0 )  THEN
223             message_string = 'errors in file NUDGING_DATA'
224             CALL message( 'nudging', 'PA0366', 1, 2, 0, 6, 0 )
225          ENDIF
226
227          DO  k = nzb, nzt+1
228             DO WHILE ( highheight < zu(k) )
229                lowheight  = highheight
230                lowtnudge  = hightnudge
231                lowunudge  = highunudge
232                lowvnudge  = highvnudge
233                lowwnudge  = highwnudge
234                lowptnudge = highptnudge
235                lowqnudge  = highqnudge
236 
237                ierrn = 0
238                READ ( finput, *, IOSTAT=ierrn )  highheight , hightnudge , &
239                                                  highunudge , highvnudge , &
240                                                  highwnudge , highptnudge, &
241                                                  highqnudge
242                IF (ierrn /= 0 )  THEN
243                   WRITE( message_string, * ) 'zu(',k,') = ', zu(k), 'm is ',&
244                        'higher than the maximum height in NUDING_DATA which ',  &
245                        'is ', lowheight, 'm. Interpolation on PALM ',           &
246                        'grid is not possible.'
247                   CALL message( 'nudging', 'PA0364', 1, 2, 0, 6, 0 )
248                ENDIF
249             ENDDO
250
251!
252!--          Interpolation of prescribed profiles in space
253
254             fac = ( highheight - zu(k) ) / ( highheight - lowheight )
255
256             tnudge(k,nt)  = fac * lowtnudge  + ( 1.0_wp - fac ) * hightnudge
257             unudge(k,nt)  = fac * lowunudge  + ( 1.0_wp - fac ) * highunudge
258             vnudge(k,nt)  = fac * lowvnudge  + ( 1.0_wp - fac ) * highvnudge
259             wnudge(k,nt)  = fac * lowwnudge  + ( 1.0_wp - fac ) * highwnudge
260             ptnudge(k,nt) = fac * lowptnudge + ( 1.0_wp - fac ) * highptnudge
261             qnudge(k,nt)  = fac * lowqnudge  + ( 1.0_wp - fac ) * highqnudge
262          ENDDO
263
264       ENDDO rloop
265
266       CLOSE ( finput )
267
268!
269!--    Prevent nudging if nudging profiles exhibt too small values
270!--    not used so far
271       lptnudge  = ANY( ABS( ptnudge ) > 1.0e-8_wp )
272       lqnudge   = ANY( ABS( qnudge )  > 1.0e-8_wp )
273       lunudge   = ANY( ABS( unudge )  > 1.0e-8_wp )
274       lvnudge   = ANY( ABS( vnudge )  > 1.0e-8_wp )
275       lwnudge   = ANY( ABS( wnudge )  > 1.0e-8_wp )
276
277    END SUBROUTINE init_nudge
278
279
280!------------------------------------------------------------------------------!
281! Description:
282! ------------
283!> @todo Missing subroutine description.
284!------------------------------------------------------------------------------!
285    SUBROUTINE calc_tnudge ( time )
286
287       USE arrays_3d,                                                          &
288           ONLY:  timenudge, tmp_tnudge, tnudge
289
290       USE control_parameters,                                                 &
291           ONLY:  dt_3d 
292
293       USE indices,                                                            &
294           ONLY:  nzb, nzt
295
296       USE kinds
297
298       IMPLICIT NONE
299
300
301       REAL(wp) ::  dtm         !<
302       REAL(wp) ::  dtp         !<
303       REAL(wp) ::  time        !<
304
305       INTEGER(iwp) ::  k   !<
306       INTEGER(iwp) ::  nt  !<
307
308       nt = 1
309       DO WHILE ( time > timenudge(nt) )
310         nt = nt+1
311       ENDDO
312       IF ( time /= timenudge(1) ) THEN
313         nt = nt-1
314       ENDIF
315
316       dtm = ( time - timenudge(nt) ) / ( timenudge(nt+1) - timenudge(nt) )
317       dtp = ( timenudge(nt+1) - time ) / ( timenudge(nt+1) - timenudge(nt) )
318
319       DO  k = nzb, nzt
320          tmp_tnudge(k) = MAX( dt_3d, tnudge(k,nt) * dtp + tnudge(k,nt+1) * dtm )
321       ENDDO
322
323    END SUBROUTINE calc_tnudge
324
325!------------------------------------------------------------------------------!
326! Description:
327! ------------
328!> Call for all grid points
329!------------------------------------------------------------------------------!
330    SUBROUTINE nudge ( time, prog_var )
331
332       USE arrays_3d,                                                          &
333           ONLY:  pt, ptnudge, q, qnudge, tend, timenudge, tmp_tnudge, tnudge, &
334                  u, unudge, v, vnudge
335
336       USE control_parameters,                                                 &
337           ONLY:  dt_3d, intermediate_timestep_count, message_string
338
339       USE indices,                                                            &
340           ONLY:  nxl, nxr, nys, nyn, nzb, nzt, wall_flags_0
341
342       USE kinds
343
344       USE statistics,                                                         &
345           ONLY:  hom, sums_ls_l, weight_substep
346
347       IMPLICIT NONE
348
349       CHARACTER (LEN=*) ::  prog_var  !<
350
351       REAL(wp) ::  tmp_tend    !<
352       REAL(wp) ::  dtm         !<
353       REAL(wp) ::  dtp         !<
354       REAL(wp) ::  time        !<
355
356       INTEGER(iwp) ::  i  !<
357       INTEGER(iwp) ::  j  !<
358       INTEGER(iwp) ::  k  !<
359       INTEGER(iwp) ::  nt  !<
360
361
362       nt = 1
363       DO WHILE ( time > timenudge(nt) )
364         nt = nt+1
365       ENDDO
366       IF ( time /= timenudge(1) ) THEN
367         nt = nt-1
368       ENDIF
369
370       dtm = ( time - timenudge(nt) ) / ( timenudge(nt+1) - timenudge(nt) )
371       dtp = ( timenudge(nt+1) - time ) / ( timenudge(nt+1) - timenudge(nt) )
372
373       SELECT CASE ( prog_var )
374
375          CASE ( 'u' )
376
377             DO  i = nxl, nxr
378                DO  j = nys, nyn
379
380                   DO  k = nzb+1, nzt
381
382                      tmp_tend = - ( hom(k,1,1,0) - ( unudge(k,nt) * dtp +     &
383                                     unudge(k,nt+1) * dtm ) ) / tmp_tnudge(k)
384
385                      tend(k,j,i) = tend(k,j,i) + tmp_tend *                   &
386                                        MERGE( 1.0_wp, 0.0_wp,                 &
387                                               BTEST( wall_flags_0(k,j,i), 1 ) )
388
389                      sums_ls_l(k,6) = sums_ls_l(k,6) + tmp_tend *             &
390                                     weight_substep(intermediate_timestep_count)
391                   ENDDO
392                 
393                   sums_ls_l(nzt+1,6) = sums_ls_l(nzt,6)
394 
395                ENDDO
396            ENDDO
397
398          CASE ( 'v' )
399
400             DO  i = nxl, nxr
401                DO  j = nys, nyn
402
403                   DO  k = nzb+1, nzt
404
405                      tmp_tend = - ( hom(k,1,2,0) - ( vnudge(k,nt) * dtp +     &
406                                     vnudge(k,nt+1) * dtm ) ) / tmp_tnudge(k)
407
408                      tend(k,j,i) = tend(k,j,i) + tmp_tend *                   &
409                                        MERGE( 1.0_wp, 0.0_wp,                 &
410                                               BTEST( wall_flags_0(k,j,i), 2 ) )
411
412                      sums_ls_l(k,7) = sums_ls_l(k,7) + tmp_tend *             &
413                                     weight_substep(intermediate_timestep_count)
414                   ENDDO
415                 
416                   sums_ls_l(nzt+1,7) = sums_ls_l(nzt,7)
417
418                ENDDO
419            ENDDO
420
421          CASE ( 'pt' )
422
423             DO  i = nxl, nxr
424                DO  j = nys, nyn
425
426                   DO  k = nzb+1, nzt
427
428                      tmp_tend = - ( hom(k,1,4,0) - ( ptnudge(k,nt) * dtp +    &
429                                     ptnudge(k,nt+1) * dtm ) ) / tmp_tnudge(k)
430
431                      tend(k,j,i) = tend(k,j,i) + tmp_tend *                   &
432                                        MERGE( 1.0_wp, 0.0_wp,                 &
433                                               BTEST( wall_flags_0(k,j,i), 0 ) )
434
435                      sums_ls_l(k,4) = sums_ls_l(k,4) + tmp_tend *             &
436                                     weight_substep(intermediate_timestep_count)
437                   ENDDO
438
439                   sums_ls_l(nzt+1,4) = sums_ls_l(nzt,4)
440
441                ENDDO
442            ENDDO
443
444          CASE ( 'q' )
445
446             DO  i = nxl, nxr
447                DO  j = nys, nyn
448
449                   DO  k = nzb+1, nzt
450
451                      tmp_tend = - ( hom(k,1,41,0) - ( qnudge(k,nt) * dtp +    &
452                                     qnudge(k,nt+1) * dtm ) ) / tmp_tnudge(k)
453
454                      tend(k,j,i) = tend(k,j,i) + tmp_tend *                   &
455                                        MERGE( 1.0_wp, 0.0_wp,                 &
456                                               BTEST( wall_flags_0(k,j,i), 0 ) )
457
458                      sums_ls_l(k,5) = sums_ls_l(k,5) + tmp_tend *             &
459                                     weight_substep(intermediate_timestep_count)
460                   ENDDO
461                 
462                   sums_ls_l(nzt+1,5) = sums_ls_l(nzt,5)
463
464                ENDDO
465            ENDDO
466
467          CASE DEFAULT
468             message_string = 'unknown prognostic variable "' // prog_var // '"'
469             CALL message( 'nudge', 'PA0367', 1, 2, 0, 6, 0 )
470
471       END SELECT
472
473    END SUBROUTINE nudge
474
475
476!------------------------------------------------------------------------------!
477! Description:
478! ------------
479!> Call for grid point i,j
480!------------------------------------------------------------------------------!
481
482    SUBROUTINE nudge_ij( i, j, time, prog_var )
483
484       USE arrays_3d,                                                          &
485           ONLY:  pt, ptnudge, q, qnudge, tend, timenudge, tmp_tnudge, tnudge, &
486                  u, unudge, v, vnudge
487
488       USE control_parameters,                                                 &
489           ONLY:  dt_3d, intermediate_timestep_count, message_string
490
491       USE indices,                                                            &
492           ONLY:  nxl, nxr, nys, nyn, nzb, nzt, wall_flags_0
493
494       USE kinds
495
496       USE statistics,                                                         &
497           ONLY:  hom, sums_ls_l, weight_substep
498
499       IMPLICIT NONE
500
501
502       CHARACTER (LEN=*) ::  prog_var  !<
503
504       REAL(wp) ::  tmp_tend    !<
505       REAL(wp) ::  dtm         !<
506       REAL(wp) ::  dtp         !<
507       REAL(wp) ::  time        !<
508
509       INTEGER(iwp) ::  i  !<
510       INTEGER(iwp) ::  j  !<
511       INTEGER(iwp) ::  k  !<
512       INTEGER(iwp) ::  nt  !<
513
514
515       nt = 1
516       DO WHILE ( time > timenudge(nt) )
517         nt = nt+1
518       ENDDO
519       IF ( time /= timenudge(1) )  THEN
520         nt = nt-1
521       ENDIF
522
523       dtm = ( time - timenudge(nt) ) / ( timenudge(nt+1) - timenudge(nt) )
524       dtp = ( timenudge(nt+1) - time ) / ( timenudge(nt+1) - timenudge(nt) )
525
526       SELECT CASE ( prog_var )
527
528          CASE ( 'u' )
529
530             DO  k = nzb+1, nzt
531
532                tmp_tend = - ( hom(k,1,1,0) - ( unudge(k,nt) * dtp +           &
533                               unudge(k,nt+1) * dtm ) ) / tmp_tnudge(k)
534
535                tend(k,j,i) = tend(k,j,i) + tmp_tend *                         &
536                                        MERGE( 1.0_wp, 0.0_wp,                 &
537                                               BTEST( wall_flags_0(k,j,i), 1 ) )
538
539                sums_ls_l(k,6) = sums_ls_l(k,6) + tmp_tend                     &
540                                 * weight_substep(intermediate_timestep_count)
541             ENDDO
542
543             sums_ls_l(nzt+1,6) = sums_ls_l(nzt,6)
544
545          CASE ( 'v' )
546
547             DO  k = nzb+1, nzt
548
549                tmp_tend = - ( hom(k,1,2,0) - ( vnudge(k,nt) * dtp +           &
550                               vnudge(k,nt+1) * dtm ) ) / tmp_tnudge(k)
551
552                tend(k,j,i) = tend(k,j,i) + tmp_tend *                         &
553                                        MERGE( 1.0_wp, 0.0_wp,                 &
554                                               BTEST( wall_flags_0(k,j,i), 2 ) )
555
556                sums_ls_l(k,7) = sums_ls_l(k,7) + tmp_tend                     &
557                                 * weight_substep(intermediate_timestep_count)
558             ENDDO
559
560             sums_ls_l(nzt+1,7) = sums_ls_l(nzt,7)
561
562          CASE ( 'pt' )
563
564             DO  k = nzb+1, nzt
565
566                tmp_tend = - ( hom(k,1,4,0) - ( ptnudge(k,nt) * dtp +          &
567                               ptnudge(k,nt+1) * dtm ) ) / tmp_tnudge(k)
568
569                tend(k,j,i) = tend(k,j,i) + tmp_tend *                         &
570                                        MERGE( 1.0_wp, 0.0_wp,                 &
571                                               BTEST( wall_flags_0(k,j,i), 0 ) )
572
573                sums_ls_l(k,4) = sums_ls_l(k,4) + tmp_tend                     &
574                                 * weight_substep(intermediate_timestep_count)
575             ENDDO
576
577             sums_ls_l(nzt+1,4) = sums_ls_l(nzt,4)
578
579
580          CASE ( 'q' )
581
582             DO  k = nzb+1, nzt
583
584                tmp_tend = - ( hom(k,1,41,0) - ( qnudge(k,nt) * dtp +          &
585                               qnudge(k,nt+1) * dtm ) ) / tmp_tnudge(k)
586
587                tend(k,j,i) = tend(k,j,i) + tmp_tend *                         &
588                                        MERGE( 1.0_wp, 0.0_wp,                 &
589                                               BTEST( wall_flags_0(k,j,i), 0 ) )
590
591                sums_ls_l(k,5) = sums_ls_l(k,5) + tmp_tend                     &
592                                 * weight_substep(intermediate_timestep_count)
593             ENDDO
594
595             sums_ls_l(nzt+1,5) = sums_ls_l(nzt,5)
596
597          CASE DEFAULT
598             message_string = 'unknown prognostic variable "' // prog_var // '"'
599             CALL message( 'nudge', 'PA0367', 1, 2, 0, 6, 0 )
600
601       END SELECT
602
603
604    END SUBROUTINE nudge_ij
605
606
607!------------------------------------------------------------------------------!
608! Description:
609! ------------
610!> @todo Missing subroutine description.
611!------------------------------------------------------------------------------!
612    SUBROUTINE nudge_ref ( time )
613
614       USE arrays_3d,                                                          &
615           ONLY:  time_vert, ptnudge, pt_init, qnudge, q_init, unudge, u_init, &
616                  vnudge, v_init
617
618       USE kinds
619
620
621       IMPLICIT NONE
622
623       INTEGER(iwp) ::  nt                    !<
624
625       REAL(wp)             ::  fac           !<
626       REAL(wp), INTENT(in) ::  time          !<
627
628!
629!--    Interpolation in time of NUDGING_DATA for pt_init and q_init. This is
630!--    needed for correct upper boundary conditions for pt and q and in case that
631!      large scale subsidence as well as scalar Rayleigh-damping are used
632       nt = 1
633       DO WHILE ( time > time_vert(nt) )
634          nt = nt + 1
635       ENDDO
636       IF ( time /= time_vert(nt) )  THEN
637        nt = nt - 1
638       ENDIF
639
640       fac = ( time-time_vert(nt) ) / ( time_vert(nt+1)-time_vert(nt) )
641
642       pt_init = ptnudge(:,nt) + fac * ( ptnudge(:,nt+1) - ptnudge(:,nt) )
643       q_init  = qnudge(:,nt) + fac * ( qnudge(:,nt+1) - qnudge(:,nt) )
644       u_init  = unudge(:,nt) + fac * ( unudge(:,nt+1) - unudge(:,nt) )
645       v_init  = vnudge(:,nt) + fac * ( vnudge(:,nt+1) - vnudge(:,nt) )
646
647    END SUBROUTINE nudge_ref
648
649 END MODULE nudge_mod
Note: See TracBrowser for help on using the repository browser.