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 @ 2082

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

Improve the merge of TRA-TRC, see ticket #717

  • Property svn:keywords set to Id
File size: 9.4 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      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts) ::   ztsn
70      !!--------------------------------------------------------------------
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      ztsn(:,:,:,jp_tem) = tn (:,:,:)
86      ztsn(:,:,:,jp_sal) = sn0(:,:,:)
87      CALL eos( ztsn, zrhd )                       ! now in situ density using initial salinity
88      !
89      zbotpres(:,:) = 0.e0                            ! no atmospheric surface pressure, levitating sea-ice
90      DO jk = 1, jpkm1
91         zbotpres(:,:) = zbotpres(:,:) + fse3t(:,:,jk) * zrhd(:,:,jk)
92      END DO
93      IF( .NOT. lk_vvl )   zbotpres(:,:) = zbotpres(:,:) + sshn(:,:) * zrhd(:,:,1)
94      !                                         
95      zarho = SUM( area(:,:) * zbotpres(:,:) ) 
96      IF( lk_mpp )   CALL mpp_sum( zarho )
97      zssh_steric = - zarho / area_tot
98      CALL iom_put( 'sshthster', zssh_steric )
99     
100      !                                         ! steric sea surface height
101      CALL eos( tsn, zrhd, zrhop )                 ! now in situ and potential density
102      zrhop(:,:,jpk) = 0.e0
103      CALL iom_put( 'rhop', zrhop )
104      !
105      zbotpres(:,:) = 0.e0                            ! no atmospheric surface pressure, levitating sea-ice
106      DO jk = 1, jpkm1
107         zbotpres(:,:) = zbotpres(:,:) + fse3t(:,:,jk) * zrhd(:,:,jk)
108      END DO
109      IF( .NOT. lk_vvl )   zbotpres(:,:) = zbotpres(:,:) + sshn(:,:) * zrhd(:,:,1)
110      !   
111      zarho = SUM( area(:,:) * zbotpres(:,:) ) 
112      IF( lk_mpp )   CALL mpp_sum( zarho )
113      zssh_steric = - zarho / area_tot
114      CALL iom_put( 'sshsteric', zssh_steric )
115     
116      !                                         ! ocean bottom pressure
117      zztmp = rau0 * grav * 1.e-4                     ! recover pressure from pressure anomaly and cover to dbar = 1.e4 Pa
118      zbotpres(:,:) = zztmp * ( zbotpres(:,:) + sshn(:,:) + thick0(:,:) )
119      CALL iom_put( 'botpres', zbotpres )
120
121      !                                         ! Mean density anomalie, temperature and salinity
122      ztemp = 0.e0
123      zsal  = 0.e0
124      DO jk = 1, jpkm1
125         DO jj = 1, jpj
126            DO ji = 1, jpi
127               zztmp = area(ji,jj) * fse3t(ji,jj,jk)
128               ztemp = ztemp + zztmp * tn  (ji,jj,jk)
129               zsal  = zsal  + zztmp * sn  (ji,jj,jk)
130            END DO
131         END DO
132      END DO
133      IF( .NOT. lk_vvl ) THEN
134         ztemp = ztemp + SUM( zarea_ssh(:,:) * tn  (:,:,1) )
135         zsal  = zsal  + SUM( zarea_ssh(:,:) * sn  (:,:,1) )
136      ENDIF
137      IF( lk_mpp ) THEN 
138         CALL mpp_sum( ztemp )
139         CALL mpp_sum( zsal  )
140      END IF
141      !
142      zmass = rau0 * ( zarho + zvol )                 ! total mass of liquid seawater
143      ztemp = ztemp / zvol                            ! potential temperature in liquid seawater
144      zsal  = zsal  / zvol                            ! Salinity of liquid seawater
145      !
146      CALL iom_put( 'masstot', zmass )
147      CALL iom_put( 'temptot', ztemp )
148      CALL iom_put( 'saltot' , zsal  )
149      !
150   END SUBROUTINE dia_ar5
151
152
153   SUBROUTINE dia_ar5_init
154      !!----------------------------------------------------------------------
155      !!                  ***  ROUTINE dia_ar5_init  ***
156      !!                   
157      !! ** Purpose :   initialization of ....
158      !!
159      !! ** Method  :   blah blah blah ...
160      !!
161      !! ** input   :   Namlist namexa
162      !!
163      !! ** Action  :   ... 
164      !!----------------------------------------------------------------------
165      INTEGER  ::   inum
166      INTEGER  ::   ik
167      INTEGER  ::   ji, jj, jk  ! dummy loop indices
168      REAL(wp) ::   zztmp 
169      REAL(wp), DIMENSION(jpi,jpj,jpk, 2) ::   zsaldta   ! Jan/Dec levitus salinity
170      !!----------------------------------------------------------------------
171      !
172      area(:,:) = e1t(:,:) * e2t(:,:) * tmask_i(:,:)
173
174      area_tot = SUM( area(:,:) )   ;   IF( lk_mpp )   CALL mpp_sum( area_tot )
175
176      vol0        = 0.e0
177      thick0(:,:) = 0.e0
178      DO jk = 1, jpkm1
179         vol0        = vol0        + SUM( area (:,:) * tmask(:,:,jk) * fse3t_0(:,:,jk) )
180         thick0(:,:) = thick0(:,:) +    tmask_i(:,:) * tmask(:,:,jk) * fse3t_0(:,:,jk)
181      END DO
182      IF( lk_mpp )   CALL mpp_sum( vol0 )
183     
184      CALL iom_open ( 'data_1m_salinity_nomask', inum )
185      CALL iom_get  ( inum, jpdom_data, 'vosaline', zsaldta(:,:,:,1), 1  )
186      CALL iom_get  ( inum, jpdom_data, 'vosaline', zsaldta(:,:,:,2), 12 )
187      CALL iom_close( inum )
188      sn0(:,:,:) = 0.5 * ( zsaldta(:,:,:,1) + zsaldta(:,:,:,2) )       
189      sn0(:,:,:) = sn0(:,:,:)*tmask(:,:,:)
190      IF( ln_zps ) THEN               ! z-coord. partial steps
191         DO jj = 1, jpj               ! interpolation of salinity at the last ocean level (i.e. the partial step)
192            DO ji = 1, jpi
193               ik = mbathy(ji,jj) - 1
194               IF( ik > 2 ) THEN
195                  zztmp = ( gdept_0(ik) - fsdept_0(ji,jj,ik) ) / ( gdept_0(ik) - gdept_0(ik-1) )
196                  sn0(ji,jj,ik) = (1.-zztmp) * sn0(ji,jj,ik) + zztmp * sn0(ji,jj,ik-1)
197               ENDIF
198            END DO
199         END DO
200      ENDIF
201      !
202   END SUBROUTINE dia_ar5_init
203
204#else
205   !!----------------------------------------------------------------------
206   !!   Default option :                                         NO diaar5
207   !!----------------------------------------------------------------------
208
209   LOGICAL, PUBLIC, PARAMETER :: lk_diaar5 = .FALSE.   ! coupled flag
210
211CONTAINS
212
213   SUBROUTINE dia_ar5( kt )   ! Empty routine
214      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
215      WRITE(*,*) 'dia_ar5: You should not have seen this print! error?', kt
216   END SUBROUTINE dia_ar5
217#endif
218
219   !!======================================================================
220END MODULE diaar5
Note: See TracBrowser for help on using the repository browser.