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_r2006_merge_TRA_TRC/NEMO/OPA_SRC/DIA – NEMO

source: branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/DIA/diaar5.F90 @ 2027

Last change on this file since 2027 was 2027, checked in by cetlod, 14 years ago

Reorganisation of the initialisation phase, see ticket:695

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