ROMS
Loading...
Searching...
No Matches
ana_diag.h
Go to the documentation of this file.
1!!
2 SUBROUTINE ana_diag (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 is provided so the USER can compute any specialized !
12! diagnostics. If activated, this routine is call at end of every !
13! 3D-equations timestep. !
14! !
15!=======================================================================
16!
17 USE mod_param
18 USE mod_ncparam
19 USE mod_ocean
20!
21! Imported variable declarations.
22!
23 integer, intent(in) :: ng, tile, model
24!
25! Local variable declarations.
26!
27 character (len=*), parameter :: MyFile = &
28 & __FILE__
29!
30#include "tile.h"
31!
32 CALL ana_diag_tile (ng, tile, model, &
33 & lbi, ubi, lbj, ubj, &
34 & imins, imaxs, jmins, jmaxs, &
35#ifdef SOLVE3D
36 & ocean(ng) % u, &
37 & ocean(ng) % v, &
38#endif
39 & ocean(ng) % ubar, &
40 & ocean(ng) % vbar)
41!
42! Set analytical header file name used.
43!
44#ifdef DISTRIBUTE
45 IF (lanafile) THEN
46#else
47 IF (lanafile.and.(tile.eq.0)) THEN
48#endif
49 ananame( 5)=myfile
50 END IF
51!
52 RETURN
53 END SUBROUTINE ana_diag
54!
55!***********************************************************************
56 SUBROUTINE ana_diag_tile (ng, tile, model, &
57 & LBi, UBi, LBj, UBj, &
58 & IminS, ImaxS, JminS, JmaxS, &
59#ifdef SOLVE3D
60 & u, v, &
61#endif
62 & ubar, vbar)
63!***********************************************************************
64!
65 USE mod_param
66 USE mod_iounits
67 USE mod_scalars
68#ifdef SEAMOUNT
69 USE mod_stepping
70#endif
71!
72! Imported variable declarations.
73!
74 integer, intent(in) :: ng, tile, model
75 integer, intent(in) :: LBi, UBi, LBj, UBj
76 integer, intent(in) :: IminS, ImaxS, JminS, JmaxS
77!
78#ifdef ASSUMED_SHAPE
79# ifdef SOLVE3D
80 real(r8), intent(in) :: u(LBi:,LBj:,:,:)
81 real(r8), intent(in) :: v(LBi:,LBj:,:,:)
82# endif
83 real(r8), intent(in) :: ubar(LBi:,LBj:,:)
84 real(r8), intent(in) :: vbar(LBi:,LBj:,:)
85#else
86# ifdef SOLVE3D
87 real(r8), intent(in) :: u(LBi:UBi,LBj:UBj,N(ng),2)
88 real(r8), intent(in) :: v(LBi:UBi,LBj:UBj,N(ng),2)
89# endif
90 real(r8), intent(in) :: ubar(LBi:UBi,LBj:UBj,:)
91 real(r8), intent(in) :: vbar(LBi:UBi,LBj:UBj,:)
92#endif
93!
94! Local variable declarations.
95!
96 integer :: i, io_error, j, k
97!
98 real(r8) :: umax, ubarmax, vmax, vbarmax
99!
100 character (len=256) :: io_errmsg
101
102#include "set_bounds.h"
103!
104!-----------------------------------------------------------------------
105! Compute user diagnostics.
106!-----------------------------------------------------------------------
107!
108#ifdef SEAMOUNT
109
110! Open USER file.
111!
112 IF (iic(ng).eq.ntstart(ng)) THEN
113 OPEN (usrout,file=usrname,form='formatted',status='unknown', &
114 & iostat=io_err, iomsg=io_errmsg)
115 IF (io_err.ne.0) THEN
116 WRITE (stdout,10) usrname, trim(io_errmsg)
117 exit_flag=5
118 RETURN
119 10 FORMAT (' ANA_DIAG - unable to open output file: ',a, &
120 /12x,'ERROR: ',a)
121 END IF
122 END IF
123!
124! Write out maximum values of velocity.
125!
126 umax=0.0_r8
127 vmax=0.0_r8
128 ubarmax=0.0_r8
129 vbarmax=0.0_r8
130 DO k=1,n(ng)
131 DO j=0,mm(ng)+1
132 DO i=1,lm(ng)+1
133 umax=max(umax,u(i,j,k,nnew(ng)))
134 END DO
135 END DO
136 DO j=1,mm(ng)+1
137 DO i=0,lm(ng)+1
138 vmax=max(vmax,v(i,j,k,nnew(ng)))
139 END DO
140 END DO
141 END DO
142 DO j=0,mm(ng)+1
143 DO i=1,lm(ng)+1
144 ubarmax=max(ubarmax,ubar(i,j,knew(ng)))
145 END DO
146 END DO
147 DO j=1,mm(ng)+1
148 DO i=0,lm(ng)+1
149 vbarmax=max(vbarmax,vbar(i,j,knew(ng)))
150 END DO
151 END DO
152!
153! Write out maximum values on velocity.
154!
155 WRITE (usrout,20) tdays(ng), ubarmax, vbarmax, umax, vmax
156 20 FORMAT (2x,f13.6,2x,1pe13.6,2x,1pe13.6,2x,1pe13.6,2x,1pe13.6)
157#endif
158!
159 RETURN
160 END SUBROUTINE ana_diag_tile
subroutine ana_diag(ng, tile, model)
Definition ana_diag.h:3
subroutine ana_diag_tile(ng, tile, model, lbi, ubi, lbj, ubj, imins, imaxs, jmins, jmaxs, u, v, ubar, vbar)
Definition ana_diag.h:63
integer usrout
character(len=256) usrname
integer stdout
logical lanafile
character(len=256), dimension(39) ananame
type(t_ocean), dimension(:), allocatable ocean
Definition mod_ocean.F:351
integer, dimension(:), allocatable lm
Definition mod_param.F:455
integer, dimension(:), allocatable mm
Definition mod_param.F:456
integer, dimension(:), allocatable iic
real(dp), dimension(:), allocatable tdays
integer exit_flag
integer, dimension(:), allocatable ntstart
integer, dimension(:), allocatable knew
integer, dimension(:), allocatable nnew