ROMS
Loading...
Searching...
No Matches
ana_passive.h
Go to the documentation of this file.
1!!
2 SUBROUTINE ana_passive (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 initial conditions for passive inert tracers !
12! using analytical expressions. !
13! !
14!=======================================================================
15!
16 USE mod_param
17 USE mod_ncparam
18 USE mod_ocean
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_passive_tile (ng, tile, model, &
32 & lbi, ubi, lbj, ubj, &
33 & imins, imaxs, jmins, jmaxs, &
34 & ocean(ng) % t)
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(18)=myfile
44 END IF
45!
46 RETURN
47 END SUBROUTINE ana_passive
48!
49!***********************************************************************
50 SUBROUTINE ana_passive_tile (ng, tile, model, &
51 & LBi, UBi, LBj, UBj, &
52 & IminS, ImaxS, JminS, JmaxS, &
53 & t)
54!***********************************************************************
55!
56 USE mod_param
57 USE mod_scalars
58!
59! Imported variable declarations.
60!
61 integer, intent(in) :: ng, tile, model
62 integer, intent(in) :: LBi, UBi, LBj, UBj
63 integer, intent(in) :: IminS, ImaxS, JminS, JmaxS
64!
65#ifdef ASSUMED_SHAPE
66 real(r8), intent(out) :: t(LBi:,LBj:,:,:,:)
67#else
68 real(r8), intent(out) :: t(LBi:UBi,LBj:UBj,N(ng),3,NT(ng))
69#endif
70!
71! Local variable declarations.
72!
73 integer :: i, iage, ip, itrc, j, k
74
75#include "set_bounds.h"
76!
77!-----------------------------------------------------------------------
78! Set analytical initial conditions for passive inert tracers.
79!-----------------------------------------------------------------------
80!
81#if defined MY_APPLICATION
82# ifdef AGE_MEAN
83 DO ip=1,npt,2
84 itrc=inert(ip)
85 iage=inert(ip+1)
86 DO k=1,n(ng)
87 DO j=jstrt,jendt
88 DO i=istrt,iendt
89 t(i,j,k,1,itrc)=???
90 t(i,j,k,2,itrc)=t(i,j,k,1,itrc)
91 t(i,j,k,1,iage)=0.0_r8
92 t(i,j,k,2,iage)=t(i,j,k,1,iage)
93 END DO
94 END DO
95 END DO
96 END DO
97# else
98 DO ip=1,npt
99 itrc=inert(ip)
100 DO k=1,n(ng)
101 DO j=jstrt,jendt
102 DO i=istrt,iendt
103 t(i,j,k,1,itrc)=???
104 t(i,j,k,2,itrc)=t(i,j,k,1,itrc)
105 END DO
106 END DO
107 END DO
108 END DO
109# endif
110#else
111 ana_passive.h: no values provided for t(:,:,:,1,inert(itrc))
112#endif
113!
114 RETURN
115 END SUBROUTINE ana_passive_tile
subroutine ana_passive_tile(ng, tile, model, lbi, ubi, lbj, ubj, imins, imaxs, jmins, jmaxs, t)
Definition ana_passive.h:54
subroutine ana_passive(ng, tile, model)
Definition ana_passive.h:3
logical lanafile
character(len=256), dimension(39) ananame
type(t_ocean), dimension(:), allocatable ocean
Definition mod_ocean.F:351
integer npt
Definition mod_param.F:505
integer, dimension(:), pointer inert