ROMS
Loading...
Searching...
No Matches
ana_pair.h
Go to the documentation of this file.
1!!
2 SUBROUTINE ana_pair (ng, tile, model)
3!
4!! git $Id$
5!!======================================================================
6!! Copyright (c) 2002-2025 The ROMS Group !
7!! Licensed under a MIT/X style license !
8!! See License_ROMS.md !
9!=======================================================================
10! !
11! This routine sets surface air pressure (mb) using an analytical !
12! expression. !
13! !
14!=======================================================================
15!
16 USE mod_param
17 USE mod_forces
18 USE mod_ncparam
19!
20! Imported variable declarations.
21!
22 integer, intent(in) :: ng, tile, model
23!
24! Local variable declarations.
25!
26 character (len=*), parameter :: MyFile = &
27 & __FILE__
28!
29#include "tile.h"
30!
31 CALL ana_pair_tile (ng, tile, model, &
32 & lbi, ubi, lbj, ubj, &
33 & imins, imaxs, jmins, jmaxs, &
34 & forces(ng) % Pair)
35!
36! Set analytical header file name used.
37!
38#ifdef DISTRIBUTE
39 IF (lanafile) THEN
40#else
41 IF (lanafile.and.(tile.eq.0)) THEN
42#endif
43 ananame(17)=myfile
44 END IF
45!
46 RETURN
47 END SUBROUTINE ana_pair
48!
49!***********************************************************************
50 SUBROUTINE ana_pair_tile (ng, tile, model, &
51 & LBi, UBi, LBj, UBj, &
52 & IminS, ImaxS, JminS, JmaxS, &
53 & Pair)
54!***********************************************************************
55!
56 USE mod_param
57 USE mod_scalars
58!
60#ifdef DISTRIBUTE
62#endif
63!
64! Imported variable declarations.
65!
66 integer, intent(in) :: ng, tile, model
67 integer, intent(in) :: LBi, UBi, LBj, UBj
68 integer, intent(in) :: IminS, ImaxS, JminS, JmaxS
69!
70#ifdef ASSUMED_SHAPE
71 real(r8), intent(out) :: Pair(LBi:,LBj:)
72#else
73 real(r8), intent(out) :: Pair(LBi:UBi,LBj:UBj)
74#endif
75!
76! Local variable declarations.
77!
78 integer :: i, j
79
80#include "set_bounds.h"
81!
82!-----------------------------------------------------------------------
83! Set analytical surface air pressure (mb).
84! (1 mb = 100 Pa = 1 hPa, 1 bar = 1.0e+5 N/m2 = 1.0e+5 dynes/cm2).
85!-----------------------------------------------------------------------
86!
87#if defined BENCHMARK
88 DO j=jstrt,jendt
89 DO i=istrt,iendt
90 pair(i,j)=1025.0_r8
91 END DO
92 END DO
93#elif defined BL_TEST
94 DO j=jstrt,jendt
95 DO i=istrt,iendt
96 pair(i,j)=1013.48_r8
97 END DO
98 END DO
99#else
100 ana_pair.h: no values provided for pair.
101#endif
102!
103! Exchange boundary data.
104!
105 IF (ewperiodic(ng).or.nsperiodic(ng)) THEN
106 CALL exchange_r2d_tile (ng, tile, &
107 & lbi, ubi, lbj, ubj, &
108 & pair)
109 END IF
110
111#ifdef DISTRIBUTE
112 CALL mp_exchange2d (ng, tile, model, 1, &
113 & lbi, ubi, lbj, ubj, &
114 & nghostpoints, &
115 & ewperiodic(ng), nsperiodic(ng), &
116 & pair)
117#endif
118!
119 RETURN
120 END SUBROUTINE ana_pair_tile
subroutine ana_pair(ng, tile, model)
Definition ana_pair.h:3
subroutine ana_pair_tile(ng, tile, model, lbi, ubi, lbj, ubj, imins, imaxs, jmins, jmaxs, pair)
Definition ana_pair.h:54
subroutine exchange_r2d_tile(ng, tile, lbi, ubi, lbj, ubj, a)
type(t_forces), dimension(:), allocatable forces
Definition mod_forces.F:554
logical lanafile
character(len=256), dimension(39) ananame
integer nghostpoints
Definition mod_param.F:710
logical, dimension(:), allocatable ewperiodic
logical, dimension(:), allocatable nsperiodic
subroutine mp_exchange2d(ng, tile, model, nvar, lbi, ubi, lbj, ubj, nghost, ew_periodic, ns_periodic, a, b, c, d)