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.
limdiahsb.F90 in trunk/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: trunk/NEMOGCM/NEMO/LIM_SRC_3/limdiahsb.F90 @ 7881

Last change on this file since 7881 was 7646, checked in by timgraham, 7 years ago

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

  • Property svn:keywords set to Id
File size: 14.1 KB
Line 
1MODULE limdiahsb
2   !!======================================================================
3   !!                       ***  MODULE limdia_hsb   ***
4   !!  LIM-3 sea ice model :   diagnostics of ice model
5   !!======================================================================
6   !! History :  3.4  ! 2012-10  (C. Rousset)  original code
7   !!----------------------------------------------------------------------
8#if defined key_lim3
9   !!----------------------------------------------------------------------
10   !!   'key_lim3'                                       LIM3 sea-ice model
11   !!----------------------------------------------------------------------
12   !!   lim_dia_hsb        : computation and output of the time evolution of keys variables
13   !!   lim_dia_hsb_init   : initialization and namelist read
14   !!----------------------------------------------------------------------
15   USE ice             ! LIM-3: sea-ice variable
16   USE dom_oce         ! ocean domain
17   USE sbc_oce         ! surface boundary condition: ocean fields
18   USE sbc_ice         ! Surface boundary condition: sea-ice fields
19   USE daymod          ! model calendar
20   USE phycst          ! physical constant
21   USE in_out_manager  ! I/O manager
22   USE lib_mpp         ! MPP library
23   USE timing          ! preformance summary
24   USE iom             ! I/O manager
25   USE lib_fortran     ! glob_sum
26   USE limrst          ! ice restart
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   lim_diahsb        ! routine called by ice_step.F90
32   PUBLIC   lim_diahsb_init   ! routine called in sbcice_lim.F90
33
34   REAL(wp), DIMENSION(:,:), ALLOCATABLE ::   vol_loc_ini, sal_loc_ini, tem_loc_ini ! initial volume, salt and heat contents
35   REAL(wp)                              ::   frc_sal, frc_voltop, frc_volbot, frc_temtop, frc_tembot  ! global forcing trends
36   
37   !! * Substitutions
38#  include "vectopt_loop_substitute.h90"
39
40   !!----------------------------------------------------------------------
41   !! NEMO/OPA 3.4 , NEMO Consortium (2012)
42   !! $Id$
43   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
44   !!----------------------------------------------------------------------
45
46CONTAINS
47
48   SUBROUTINE lim_diahsb( kt )
49      !!---------------------------------------------------------------------------
50      !!                  ***  ROUTINE lim_diahsb  ***
51      !!     
52      !! ** Purpose: Compute the ice global heat content, salt content and volume conservation
53      !!
54      !!---------------------------------------------------------------------------
55      INTEGER, INTENT(in) :: kt    ! number of iteration
56      !!
57      real(wp)   ::   zbg_ivol, zbg_svol, zbg_area, zbg_isal, zbg_item ,zbg_stem
58      REAL(wp)   ::   z_frc_voltop, z_frc_volbot, z_frc_sal, z_frc_temtop, z_frc_tembot 
59      REAL(wp)   ::   zdiff_vol, zdiff_sal, zdiff_tem 
60      !!---------------------------------------------------------------------------
61      IF( nn_timing == 1 )   CALL timing_start('lim_diahsb')
62
63      ! ----------------------- !
64      ! 1 -  Contents !
65      ! ----------------------- !
66      zbg_ivol = glob_sum( vt_i(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )                  ! ice volume (km3)
67      zbg_svol = glob_sum( vt_s(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )                  ! snow volume (km3)
68      zbg_area = glob_sum( at_i(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-6 )                  ! area (km2)
69      zbg_isal = glob_sum( SUM( smv_i(:,:,:), dim=3 ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 ) ! salt content (pss*km3)
70      zbg_item = glob_sum( et_i * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 )                      ! heat content (1.e20 J)
71      zbg_stem = glob_sum( et_s * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 )                      ! heat content (1.e20 J)
72     
73      ! ---------------------------!
74      ! 2 - Trends due to forcing  !
75      ! ---------------------------!
76      z_frc_volbot = r1_rau0 * glob_sum( - ( wfx_ice(:,:) + wfx_snw(:,:) + wfx_err_sub(:,:) ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )  ! freshwater flux ice/snow-ocean
77      z_frc_voltop = r1_rau0 * glob_sum( - ( wfx_sub(:,:) + wfx_spr(:,:) ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )                     ! freshwater flux ice/snow-atm
78      z_frc_sal    = r1_rau0 * glob_sum( - sfx(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )                                            ! salt fluxes ice/snow-ocean
79      z_frc_tembot =           glob_sum( hfx_out(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 )                                         ! heat on top of ocean (and below ice)
80      z_frc_temtop =           glob_sum( hfx_in (:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 )                                         ! heat on top of ice-coean
81      !
82      frc_voltop  = frc_voltop  + z_frc_voltop  * rdt_ice ! km3
83      frc_volbot  = frc_volbot  + z_frc_volbot  * rdt_ice ! km3
84      frc_sal     = frc_sal     + z_frc_sal     * rdt_ice ! km3*pss
85      frc_temtop  = frc_temtop  + z_frc_temtop  * rdt_ice ! 1.e20 J
86      frc_tembot  = frc_tembot  + z_frc_tembot  * rdt_ice ! 1.e20 J
87           
88      ! ----------------------- !
89      ! 3 -  Content variations !
90      ! ----------------------- !
91      zdiff_vol = r1_rau0 * glob_sum( ( rhoic * vt_i(:,:) + rhosn * vt_s(:,:) - vol_loc_ini(:,:)  &  ! freshwater trend (km3)
92         &                            ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 ) 
93      zdiff_sal = r1_rau0 * glob_sum( ( rhoic * SUM( smv_i(:,:,:), dim=3 ) - sal_loc_ini(:,:)     &  ! salt content trend (km3*pss)
94         &                            ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )
95      zdiff_tem =           glob_sum( ( et_i(:,:) + et_s(:,:) - tem_loc_ini(:,:)                  &  ! heat content trend (1.e20 J)
96      !  &                            + SUM( qevap_ice * a_i_b, dim=3 ) &     !! clem: I think this line should be commented (but needs a check)
97         &                            ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 )
98
99      ! ----------------------- !
100      ! 4 -  Drifts             !
101      ! ----------------------- !
102      zdiff_vol = zdiff_vol - ( frc_voltop + frc_volbot )
103      zdiff_sal = zdiff_sal - frc_sal
104      zdiff_tem = zdiff_tem - ( frc_tembot - frc_temtop )
105
106      ! ----------------------- !
107      ! 5 - Diagnostics writing !
108      ! ----------------------- !
109      !
110      IF( iom_use('ibgvolume') )  CALL iom_put( 'ibgvolume' , zdiff_vol        )   ! ice/snow volume  drift            (km3 equivalent ocean water)         
111      IF( iom_use('ibgsaltco') )  CALL iom_put( 'ibgsaltco' , zdiff_sal        )   ! ice salt content drift            (psu*km3 equivalent ocean water)
112      IF( iom_use('ibgheatco') )  CALL iom_put( 'ibgheatco' , zdiff_tem        )   ! ice/snow heat content drift       (1.e20 J)
113      IF( iom_use('ibgheatfx') )  CALL iom_put( 'ibgheatfx' , zdiff_tem /      &   ! ice/snow heat flux drift          (W/m2)
114         &                                                    glob_sum( e1e2t(:,:) * tmask(:,:,1) * 1.e-20 * kt*rdt ) )
115
116      IF( iom_use('ibgfrcvoltop') )  CALL iom_put( 'ibgfrcvoltop' , frc_voltop )   ! vol  forcing ice/snw-atm          (km3 equivalent ocean water)
117      IF( iom_use('ibgfrcvolbot') )  CALL iom_put( 'ibgfrcvolbot' , frc_volbot )   ! vol  forcing ice/snw-ocean        (km3 equivalent ocean water)
118      IF( iom_use('ibgfrcsal') )     CALL iom_put( 'ibgfrcsal'    , frc_sal    )   ! sal - forcing                     (psu*km3 equivalent ocean water)   
119      IF( iom_use('ibgfrctemtop') )  CALL iom_put( 'ibgfrctemtop' , frc_temtop )   ! heat on top of ice/snw/ocean      (1.e20 J)   
120      IF( iom_use('ibgfrctembot') )  CALL iom_put( 'ibgfrctembot' , frc_tembot )   ! heat on top of ocean(below ice)   (1.e20 J)   
121      IF( iom_use('ibgfrchfxtop') )  CALL iom_put( 'ibgfrchfxtop' , frc_temtop / & ! heat on top of ice/snw/ocean      (W/m2)
122         &                                                    glob_sum( e1e2t(:,:) * tmask(:,:,1) * 1.e-20 * kt*rdt ) )
123      IF( iom_use('ibgfrchfxbot') )  CALL iom_put( 'ibgfrchfxbot' , frc_tembot / & ! heat on top of ocean(below ice)   (W/m2)
124         &                                                    glob_sum( e1e2t(:,:) * tmask(:,:,1) * 1.e-20 * kt*rdt ) )
125
126      IF( iom_use('ibgvol_tot' ) )  CALL iom_put( 'ibgvol_tot'  , zbg_ivol     )   ! ice volume                        (km3)
127      IF( iom_use('sbgvol_tot' ) )  CALL iom_put( 'sbgvol_tot'  , zbg_svol     )   ! snow volume                       (km3)
128      IF( iom_use('ibgarea_tot') )  CALL iom_put( 'ibgarea_tot' , zbg_area     )   ! ice area                          (km2)
129      IF( iom_use('ibgsalt_tot') )  CALL iom_put( 'ibgsalt_tot' , zbg_isal     )   ! ice salinity content              (pss*km3)
130      IF( iom_use('ibgheat_tot') )  CALL iom_put( 'ibgheat_tot' , zbg_item     )   ! ice heat content                  (1.e20 J)
131      IF( iom_use('sbgheat_tot') )  CALL iom_put( 'sbgheat_tot' , zbg_stem     )   ! snow heat content                 (1.e20 J)
132      !
133      IF( lrst_ice )   CALL lim_diahsb_rst( numit, 'WRITE' )
134      !
135      IF( nn_timing == 1 )   CALL timing_stop('lim_diahsb')
136      !
137   END SUBROUTINE lim_diahsb
138
139
140   SUBROUTINE lim_diahsb_init
141      !!---------------------------------------------------------------------------
142      !!                  ***  ROUTINE lim_diahsb_init  ***
143      !!     
144      !! ** Purpose: Initialization for the heat salt volume budgets
145      !!
146      !! ** Method : Compute initial heat content, salt content and volume
147      !!
148      !! ** Action : - Compute initial heat content, salt content and volume
149      !!             - Initialize forcing trends
150      !!             - Compute coefficients for conversion
151      !!---------------------------------------------------------------------------
152      INTEGER            ::   ierror   ! local integer
153      !!
154      !!NAMELIST/namicehsb/ blabla
155      !!----------------------------------------------------------------------
156      !
157      !!REWIND ( numnam_ice )              ! Read Namelist namicehsb
158      !!READ   ( numnam_ice, namicehsb )
159      !
160      IF(lwp) THEN                   ! Control print
161         WRITE(numout,*)
162         WRITE(numout,*) 'lim_diahsb_init : check the heat and salt budgets'
163         WRITE(numout,*) '~~~~~~~~~~~~'
164      ENDIF
165      !     
166      ALLOCATE( vol_loc_ini(jpi,jpj), sal_loc_ini(jpi,jpj), tem_loc_ini(jpi,jpj), STAT=ierror )
167      IF( ierror > 0 )  THEN
168         CALL ctl_stop( 'lim_diahsb: unable to allocate vol_loc_ini' )
169         RETURN
170      ENDIF
171
172      CALL lim_diahsb_rst( nstart, 'READ' )  !* read or initialize all required files
173      !
174   END SUBROUTINE lim_diahsb_init
175
176   SUBROUTINE lim_diahsb_rst( kt, cdrw )
177     !!---------------------------------------------------------------------
178     !!                   ***  ROUTINE limdia_rst  ***
179     !!                     
180     !! ** Purpose :   Read or write DIA file in restart file
181     !!
182     !! ** Method  :   use of IOM library
183     !!----------------------------------------------------------------------
184     INTEGER         , INTENT(in) ::   kt     ! ice time-step
185     CHARACTER(len=*), INTENT(in) ::   cdrw   ! "READ"/"WRITE" flag
186     !
187     !!----------------------------------------------------------------------
188     !
189     IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise
190        IF( ln_rstart ) THEN                   !* Read the restart file
191           !
192           IF(lwp) WRITE(numout,*) '~~~~~~~'
193           IF(lwp) WRITE(numout,*) ' lim_diahsb_rst read at it= ', kt,' date= ', ndastp
194           IF(lwp) WRITE(numout,*) '~~~~~~~'
195           CALL iom_get( numrir, 'frc_voltop' , frc_voltop  )
196           CALL iom_get( numrir, 'frc_volbot' , frc_volbot  )
197           CALL iom_get( numrir, 'frc_temtop' , frc_temtop  )
198           CALL iom_get( numrir, 'frc_tembot' , frc_tembot  )
199           CALL iom_get( numrir, 'frc_sal'    , frc_sal     )
200           CALL iom_get( numrir, jpdom_autoglo, 'vol_loc_ini', vol_loc_ini )
201           CALL iom_get( numrir, jpdom_autoglo, 'tem_loc_ini', tem_loc_ini )
202           CALL iom_get( numrir, jpdom_autoglo, 'sal_loc_ini', sal_loc_ini )
203        ELSE
204           IF(lwp) WRITE(numout,*) '~~~~~~~'
205           IF(lwp) WRITE(numout,*) ' lim_diahsb at initial state '
206           IF(lwp) WRITE(numout,*) '~~~~~~~'
207           ! set trends to 0
208           frc_voltop  = 0._wp                                         
209           frc_volbot  = 0._wp                                         
210           frc_temtop  = 0._wp                                                 
211           frc_tembot  = 0._wp                                                 
212           frc_sal     = 0._wp                                                 
213           ! record initial ice volume, salt and temp
214           vol_loc_ini(:,:) = rhoic * vt_i(:,:) + rhosn * vt_s(:,:)  ! ice/snow volume (kg/m2)
215           tem_loc_ini(:,:) = et_i(:,:) + et_s(:,:)                  ! ice/snow heat content (J)
216           sal_loc_ini(:,:) = rhoic * SUM( smv_i(:,:,:), dim=3 )     ! ice salt content (pss*kg/m2)
217           
218       ENDIF
219
220     ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file
221        !                                   ! -------------------
222        IF(lwp) WRITE(numout,*) '~~~~~~~'
223        IF(lwp) WRITE(numout,*) ' lim_diahsb_rst write at it= ', kt,' date= ', ndastp
224        IF(lwp) WRITE(numout,*) '~~~~~~~'
225        CALL iom_rstput( kt, nitrst, numriw, 'frc_voltop' , frc_voltop  )
226        CALL iom_rstput( kt, nitrst, numriw, 'frc_volbot' , frc_volbot  )
227        CALL iom_rstput( kt, nitrst, numriw, 'frc_temtop' , frc_temtop  )
228        CALL iom_rstput( kt, nitrst, numriw, 'frc_tembot' , frc_tembot  )
229        CALL iom_rstput( kt, nitrst, numriw, 'frc_sal'    , frc_sal     )
230        CALL iom_rstput( kt, nitrst, numriw, 'vol_loc_ini', vol_loc_ini )
231        CALL iom_rstput( kt, nitrst, numriw, 'tem_loc_ini', tem_loc_ini )
232        CALL iom_rstput( kt, nitrst, numriw, 'sal_loc_ini', sal_loc_ini )
233        !
234     ENDIF
235     !
236   END SUBROUTINE lim_diahsb_rst
237 
238#else
239   !!----------------------------------------------------------------------
240   !!   Default option :         Empty module          NO LIM sea-ice model
241   !!----------------------------------------------------------------------
242CONTAINS
243   SUBROUTINE lim_diahsb          ! Empty routine
244   END SUBROUTINE lim_diahsb
245#endif
246   !!======================================================================
247END MODULE limdiahsb
Note: See TracBrowser for help on using the repository browser.