New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
diaar5.F90 in branches/DEV_r1784_mid_year_merge_2010/NEMO/OPA_SRC/DIA – NEMO

source: branches/DEV_r1784_mid_year_merge_2010/NEMO/OPA_SRC/DIA/diaar5.F90 @ 2004

Last change on this file since 2004 was 2004, checked in by acc, 14 years ago

ticket #684 step 8: Add in changes from the trunk between revisions 1879 and the 3.2.1 tag (rev 1986)

  • Property svn:keywords set to Id
File size: 9.3 KB
Line 
1MODULE diaar5
2   !!======================================================================
3   !!                       ***  MODULE  diaar5  ***
4   !! AR5 diagnostics
5   !!======================================================================
6   !! History : 3.2  !  2009-11  (S. Masson)  Original code
7   !!----------------------------------------------------------------------
8#if defined key_diaar5
9   !!----------------------------------------------------------------------
10   !!   'key_diaar5'  :                           activate ar5 diagnotics
11   !!----------------------------------------------------------------------
12   !!   exa_mpl       : liste of module subroutine (caution, never use the
13   !!   exa_mpl_init  : name of the module for a routine)
14   !!   exa_mpl_stp   : Please try to use 3 letter block for routine names
15   !!----------------------------------------------------------------------
16   USE oce            ! ocean dynamics and active tracers
17   USE dom_oce        ! ocean space and time domain
18   USE eosbn2          ! equation of state                (eos_bn2 routine)
19   USE lib_mpp        ! distribued memory computing library
20   USE iom            ! I/O manager library
21
22   IMPLICIT NONE
23   PRIVATE
24
25   PUBLIC   dia_ar5   ! routine called in step.F90 module
26
27   LOGICAL, PUBLIC, PARAMETER :: lk_diaar5 = .TRUE.   ! coupled flag
28
29   REAL(wp)                         ::   vol0               ! ocean volume (interior domain)
30   REAL(wp)                         ::   area_tot           ! total ocean surface (interior domain)
31   REAL(wp), DIMENSION(jpi,jpj    ) ::   area               ! cell surface (interior domain)
32   REAL(wp), DIMENSION(jpi,jpj    ) ::   thick0             ! ocean thickness (interior domain)
33   REAL(wp), DIMENSION(jpi,jpj,jpk) ::   sn0                ! initial salinity
34     
35   !! * Substitutions
36#  include "domzgr_substitute.h90"
37   !!----------------------------------------------------------------------
38   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)
39   !! $Id$
40   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
41   !!----------------------------------------------------------------------
42
43CONTAINS
44
45   SUBROUTINE dia_ar5( kt )
46      !!----------------------------------------------------------------------
47      !!                    ***  ROUTINE dia_ar5  ***
48      !!
49      !! ** Purpose :   Brief description of the routine
50      !!
51      !! ** Method  :   description of the methodoloy used to achieve the
52      !!                objectives of the routine. Be as clear as possible!
53      !!
54      !! ** Action  : - first action (share memory array/varible modified
55      !!                in this routine
56      !!              - second action .....
57      !!              - .....
58      !!
59      !! References :   Author et al., Short_name_review, Year
60      !!                Give references if exist otherwise suppress these lines
61      !!----------------------------------------------------------------------
62      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
63      !!
64      INTEGER  ::   ji, jj, jk                      ! dummy loop arguments
65      REAL(wp) ::   zvolssh, zvol, zssh_steric, zztmp, zarho, ztemp, zsal, zmass
66      REAL(wp), DIMENSION(jpi,jpj    ) ::   zarea_ssh, zbotpres
67      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zrhd, zrhop
68      !!--------------------------------------------------------------------
69
70      IF( kt == nit000  )   CALL dia_ar5_init   ! Initialization (first time-step only)
71
72      CALL iom_put( 'cellthc', fse3t(:,:,:) )
73
74      zarea_ssh(:,:) = area(:,:) * sshn(:,:)
75
76      !                                         ! total volume of liquid seawater
77      zvolssh = SUM( zarea_ssh(:,:) ) 
78      IF( lk_mpp )   CALL mpp_sum( zvolssh )
79      zvol = vol0 + zvolssh
80     
81      CALL iom_put( 'voltot', zvol               )
82      CALL iom_put( 'sshtot', zvolssh / area_tot )
83
84      !                                         ! thermosteric ssh
85      CALL eos( tn, sn0, zrhd )                       ! now in situ density using initial salinity
86      !
87      zbotpres(:,:) = 0.e0                            ! no atmospheric surface pressure, levitating sea-ice
88      DO jk = 1, jpkm1
89         zbotpres(:,:) = zbotpres(:,:) + fse3t(:,:,jk) * zrhd(:,:,jk)
90      END DO
91      IF( .NOT. lk_vvl )   zbotpres(:,:) = zbotpres(:,:) + sshn(:,:) * zrhd(:,:,1)
92      !                                         
93      zarho = SUM( area(:,:) * zbotpres(:,:) ) 
94      IF( lk_mpp )   CALL mpp_sum( zarho )
95      zssh_steric = - zarho / area_tot
96      CALL iom_put( 'sshthster', zssh_steric )
97     
98      !                                         ! steric sea surface height
99      CALL eos( tn, sn, zrhd, zrhop )                 ! now in situ and potential density
100      zrhop(:,:,jpk) = 0.e0
101      CALL iom_put( 'rhop', zrhop )
102      !
103      zbotpres(:,:) = 0.e0                            ! no atmospheric surface pressure, levitating sea-ice
104      DO jk = 1, jpkm1
105         zbotpres(:,:) = zbotpres(:,:) + fse3t(:,:,jk) * zrhd(:,:,jk)
106      END DO
107      IF( .NOT. lk_vvl )   zbotpres(:,:) = zbotpres(:,:) + sshn(:,:) * zrhd(:,:,1)
108      !   
109      zarho = SUM( area(:,:) * zbotpres(:,:) ) 
110      IF( lk_mpp )   CALL mpp_sum( zarho )
111      zssh_steric = - zarho / area_tot
112      CALL iom_put( 'sshsteric', zssh_steric )
113     
114      !                                         ! ocean bottom pressure
115      zztmp = rau0 * grav * 1.e-4                     ! recover pressure from pressure anomaly and cover to dbar = 1.e4 Pa
116      zbotpres(:,:) = zztmp * ( zbotpres(:,:) + sshn(:,:) + thick0(:,:) )
117      CALL iom_put( 'botpres', zbotpres )
118
119      !                                         ! Mean density anomalie, temperature and salinity
120      ztemp = 0.e0
121      zsal  = 0.e0
122      DO jk = 1, jpkm1
123         DO jj = 1, jpj
124            DO ji = 1, jpi
125               zztmp = area(ji,jj) * fse3t(ji,jj,jk)
126               ztemp = ztemp + zztmp * tn  (ji,jj,jk)
127               zsal  = zsal  + zztmp * sn  (ji,jj,jk)
128            END DO
129         END DO
130      END DO
131      IF( .NOT. lk_vvl ) THEN
132         ztemp = ztemp + SUM( zarea_ssh(:,:) * tn  (:,:,1) )
133         zsal  = zsal  + SUM( zarea_ssh(:,:) * sn  (:,:,1) )
134      ENDIF
135      IF( lk_mpp ) THEN 
136         CALL mpp_sum( ztemp )
137         CALL mpp_sum( zsal  )
138      END IF
139      !
140      zmass = rau0 * ( zarho + zvol )                 ! total mass of liquid seawater
141      ztemp = ztemp / zvol                            ! potential temperature in liquid seawater
142      zsal  = zsal  / zvol                            ! Salinity of liquid seawater
143      !
144      CALL iom_put( 'masstot', zmass )
145      CALL iom_put( 'temptot', ztemp )
146      CALL iom_put( 'saltot' , zsal  )
147      !
148   END SUBROUTINE dia_ar5
149
150
151   SUBROUTINE dia_ar5_init
152      !!----------------------------------------------------------------------
153      !!                  ***  ROUTINE dia_ar5_init  ***
154      !!                   
155      !! ** Purpose :   initialization of ....
156      !!
157      !! ** Method  :   blah blah blah ...
158      !!
159      !! ** input   :   Namlist namexa
160      !!
161      !! ** Action  :   ... 
162      !!----------------------------------------------------------------------
163      INTEGER  ::   inum
164      INTEGER  ::   ik
165      INTEGER  ::   ji, jj, jk  ! dummy loop indices
166      REAL(wp) ::   zztmp 
167      REAL(wp), DIMENSION(jpi,jpj,jpk, 2) ::   zsaldta   ! Jan/Dec levitus salinity
168      !!----------------------------------------------------------------------
169      !
170      area(:,:) = e1t(:,:) * e2t(:,:) * tmask_i(:,:)
171
172      area_tot = SUM( area(:,:) )   ;   IF( lk_mpp )   CALL mpp_sum( area_tot )
173
174      vol0        = 0.e0
175      thick0(:,:) = 0.e0
176      DO jk = 1, jpkm1
177         vol0        = vol0        + SUM( area (:,:) * tmask(:,:,jk) * fse3t_0(:,:,jk) )
178         thick0(:,:) = thick0(:,:) +    tmask_i(:,:) * tmask(:,:,jk) * fse3t_0(:,:,jk)
179      END DO
180      IF( lk_mpp )   CALL mpp_sum( vol0 )
181     
182      CALL iom_open ( 'data_1m_salinity_nomask', inum )
183      CALL iom_get  ( inum, jpdom_data, 'vosaline', zsaldta(:,:,:,1), 1  )
184      CALL iom_get  ( inum, jpdom_data, 'vosaline', zsaldta(:,:,:,2), 12 )
185      CALL iom_close( inum )
186      sn0(:,:,:) = 0.5 * ( zsaldta(:,:,:,1) + zsaldta(:,:,:,2) )       
187      sn0(:,:,:) = sn0(:,:,:)*tmask(:,:,:)
188      IF( ln_zps ) THEN               ! z-coord. partial steps
189         DO jj = 1, jpj               ! interpolation of salinity at the last ocean level (i.e. the partial step)
190            DO ji = 1, jpi
191               ik = mbathy(ji,jj) - 1
192               IF( ik > 2 ) THEN
193                  zztmp = ( gdept_0(ik) - fsdept_0(ji,jj,ik) ) / ( gdept_0(ik) - gdept_0(ik-1) )
194                  sn0(ji,jj,ik) = (1.-zztmp) * sn0(ji,jj,ik) + zztmp * sn0(ji,jj,ik-1)
195               ENDIF
196            END DO
197         END DO
198      ENDIF
199      !
200   END SUBROUTINE dia_ar5_init
201
202#else
203   !!----------------------------------------------------------------------
204   !!   Default option :                                         NO diaar5
205   !!----------------------------------------------------------------------
206
207   LOGICAL, PUBLIC, PARAMETER :: lk_diaar5 = .FALSE.   ! coupled flag
208
209CONTAINS
210
211   SUBROUTINE dia_ar5( kt )   ! Empty routine
212      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
213      WRITE(*,*) 'dia_ar5: You should not have seen this print! error?', kt
214   END SUBROUTINE dia_ar5
215#endif
216
217   !!======================================================================
218END MODULE diaar5
Note: See TracBrowser for help on using the repository browser.