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.
icedyn_adv.F90 in NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/ICE – NEMO

source: NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/ICE/icedyn_adv.F90 @ 10314

Last change on this file since 10314 was 10069, checked in by nicolasmartin, 6 years ago

Fix mistakes of previous commit on SVN keywords property

  • Property svn:keywords set to Id
File size: 10.4 KB
Line 
1MODULE icedyn_adv
2   !!======================================================================
3   !!                       ***  MODULE icedyn_adv   ***
4   !!   sea-ice: advection
5   !!======================================================================
6   !! History :  4.0  !  2018     (many people)      SI3 [aka Sea Ice cube]
7   !!----------------------------------------------------------------------
8#if defined key_si3
9   !!----------------------------------------------------------------------
10   !!   'key_si3'                                       SI3 sea-ice model
11   !!----------------------------------------------------------------------
12   !!   ice_dyn_adv   : advection of sea ice variables
13   !!----------------------------------------------------------------------
14   USE phycst         ! physical constant
15   USE dom_oce        ! ocean domain
16   USE sbc_oce , ONLY : nn_fsbc   ! frequency of sea-ice call
17   USE ice            ! sea-ice: variables
18   USE icevar         ! sea-ice: operations
19   USE icedyn_adv_pra ! sea-ice: advection scheme (Prather)
20   USE icedyn_adv_umx ! sea-ice: advection scheme (ultimate-macho)
21   USE icectl         ! sea-ice: control prints
22   !
23   USE in_out_manager ! I/O manager
24   USE iom            ! I/O manager library
25   USE lib_mpp        ! MPP library
26   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero)
27   USE timing         ! Timing
28   USE prtctl         ! Print control
29
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC   ice_dyn_adv        ! called by icestp
34   PUBLIC   ice_dyn_adv_init   ! called by icedyn
35
36   INTEGER ::              nice_adv   ! choice of the type of advection scheme
37   !                                        ! associated indices:
38   INTEGER, PARAMETER ::   np_advPRA = 1   ! Prather scheme
39   INTEGER, PARAMETER ::   np_advUMx = 2   ! Ultimate-Macho scheme
40   !
41   ! ** namelist (namdyn_adv) **
42   LOGICAL ::   ln_adv_Pra   ! Prather        advection scheme
43   LOGICAL ::   ln_adv_UMx   ! Ultimate-Macho advection scheme
44   INTEGER ::   nn_UMx       ! order of the UMx advection scheme   
45   !
46   !! * Substitution
47#  include "vectopt_loop_substitute.h90"
48   !!----------------------------------------------------------------------
49   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
50   !! $Id$
51   !! Software governed by the CeCILL license (see ./LICENSE)
52   !!----------------------------------------------------------------------
53CONTAINS
54
55   SUBROUTINE ice_dyn_adv( kt ) 
56      !!----------------------------------------------------------------------
57      !!                   ***  ROUTINE ice_dyn_adv ***
58      !!                   
59      !! ** purpose : advection of sea ice
60      !!
61      !! ** method  : One can choose between
62      !!     a) an Ultimate-Macho scheme (with order defined by nn_UMx) => ln_adv_UMx
63      !!     b) and a second order Prather scheme => ln_adv_Pra
64      !!
65      !! ** action :
66      !!----------------------------------------------------------------------
67      INTEGER, INTENT(in) ::   kt   ! number of iteration
68      !
69      INTEGER ::   jl   ! dummy loop indice
70      REAL(wp), DIMENSION(jpi,jpj) ::   zmask  ! fraction of time step with v_i < 0
71      !!---------------------------------------------------------------------
72      !
73      IF( ln_timing )   CALL timing_start('icedyn_adv')
74      !
75      IF( kt == nit000 .AND. lwp ) THEN
76         WRITE(numout,*)
77         WRITE(numout,*) 'ice_dyn_adv: sea-ice advection'
78         WRITE(numout,*) '~~~~~~~~~~~'
79      ENDIF
80     
81      ! conservation test
82      IF( ln_icediachk )   CALL ice_cons_hsm(0, 'icedyn_adv', rdiag_v, rdiag_s, rdiag_t, rdiag_fv, rdiag_fs, rdiag_ft)
83                     
84      !----------
85      ! Advection
86      !----------
87      SELECT CASE( nice_adv )
88      !                                !-----------------------!
89      CASE( np_advUMx )                ! ULTIMATE-MACHO scheme !
90         !                             !-----------------------!
91         CALL ice_dyn_adv_umx( nn_UMx, kt, u_ice, v_ice,  &
92            &                  ato_i, v_i, v_s, sv_i, oa_i, a_i, a_ip, v_ip, e_s, e_i )
93      !                                !-----------------------!
94      CASE( np_advPRA )                ! PRATHER scheme        !
95         !                             !-----------------------!
96         CALL ice_dyn_adv_pra( kt, u_ice, v_ice,  &
97            &                  ato_i, v_i, v_s, sv_i, oa_i, a_i, a_ip, v_ip, e_s, e_i )
98      END SELECT
99
100      !----------------------------
101      ! Debug the advection schemes
102      !----------------------------
103      ! clem: At least one advection scheme above is not strictly positive => UM from 3d to 5th order
104      !       In Prather, I am not sure if the fields are bounded by 0 or not (it seems not)
105      !       In UM3-5  , advected fields are not bounded and negative values can appear.
106      !                   These values are usually very small but in some occasions they can also be non-negligible
107      !                   Therefore one needs to bound the advected fields by 0 (though this is not a clean fix)
108      !
109      ! record the negative values resulting from UMx
110      zmask(:,:) = 0._wp ! keep the init to 0 here
111      DO jl = 1, jpl
112         WHERE( v_i(:,:,jl) < 0._wp )   zmask(:,:) = 1._wp
113      END DO
114      IF( iom_use('iceneg_pres') )   CALL iom_put("iceneg_pres", zmask                                      )  ! fraction of time step with v_i < 0
115      IF( iom_use('iceneg_volu') )   CALL iom_put("iceneg_volu", SUM(MIN( v_i, 0. ), dim=3 )                )  ! negative ice volume (only)
116      IF( iom_use('iceneg_hfx' ) )   CALL iom_put("iceneg_hfx" , ( SUM(SUM( MIN( e_i(:,:,1:nlay_i,:), 0. )  &  ! negative ice heat content (only)
117         &                                                                  , dim=4 ), dim=3 ) )* r1_rdtice )  ! -- eq. heat flux [W/m2]
118      !
119      ! ==> conservation is ensured by calling this routine below,
120      !     however the global ice volume is then changed by advection (but errors are very small)
121      CALL ice_var_zapneg( ato_i, v_i, v_s, sv_i, oa_i, a_i, a_ip, v_ip, e_s, e_i )
122
123      !------------
124      ! diagnostics
125      !------------
126      diag_trp_ei(:,:) = SUM(SUM( e_i (:,:,1:nlay_i,:) - e_i_b (:,:,1:nlay_i,:), dim=4 ), dim=3 ) * r1_rdtice
127      diag_trp_es(:,:) = SUM(SUM( e_s (:,:,1:nlay_s,:) - e_s_b (:,:,1:nlay_s,:), dim=4 ), dim=3 ) * r1_rdtice
128      diag_trp_sv(:,:) = SUM(     sv_i(:,:,:)          - sv_i_b(:,:,:)                  , dim=3 ) * r1_rdtice
129      diag_trp_vi(:,:) = SUM(     v_i (:,:,:)          - v_i_b (:,:,:)                  , dim=3 ) * r1_rdtice
130      diag_trp_vs(:,:) = SUM(     v_s (:,:,:)          - v_s_b (:,:,:)                  , dim=3 ) * r1_rdtice
131      IF( iom_use('icemtrp') )   CALL iom_put( "icemtrp" , diag_trp_vi * rhoi          )   ! ice mass transport
132      IF( iom_use('snwmtrp') )   CALL iom_put( "snwmtrp" , diag_trp_vs * rhos          )   ! snw mass transport
133      IF( iom_use('salmtrp') )   CALL iom_put( "salmtrp" , diag_trp_sv * rhoi * 1.e-03 )   ! salt mass transport (kg/m2/s)
134      IF( iom_use('dihctrp') )   CALL iom_put( "dihctrp" , -diag_trp_ei                )   ! advected ice heat content (W/m2)
135      IF( iom_use('dshctrp') )   CALL iom_put( "dshctrp" , -diag_trp_es                )   ! advected snw heat content (W/m2)
136
137      ! controls
138      IF( ln_icediachk )   CALL ice_cons_hsm(1, 'icedyn_adv', rdiag_v, rdiag_s, rdiag_t, rdiag_fv, rdiag_fs, rdiag_ft) ! conservation
139      IF( ln_icectl    )   CALL ice_prt     (kt, iiceprt, jiceprt,-1, ' - ice dyn & trp - ')                           ! prints
140      IF( ln_timing    )   CALL timing_stop ('icedyn_adv')                                                             ! timing
141      !
142   END SUBROUTINE ice_dyn_adv
143
144
145   SUBROUTINE ice_dyn_adv_init
146      !!-------------------------------------------------------------------
147      !!                  ***  ROUTINE ice_dyn_adv_init  ***
148      !!
149      !! ** Purpose :   Physical constants and parameters linked to the ice
150      !!                dynamics
151      !!
152      !! ** Method  :   Read the namdyn_adv namelist and check the ice-dynamic
153      !!                parameter values called at the first timestep (nit000)
154      !!
155      !! ** input   :   Namelist namdyn_adv
156      !!-------------------------------------------------------------------
157      INTEGER ::   ios, ioptio   ! Local integer output status for namelist read
158      !!
159      NAMELIST/namdyn_adv/ ln_adv_Pra, ln_adv_UMx, nn_UMx
160      !!-------------------------------------------------------------------
161      !
162      REWIND( numnam_ice_ref )         ! Namelist namdyn_adv in reference namelist : Ice dynamics
163      READ  ( numnam_ice_ref, namdyn_adv, IOSTAT = ios, ERR = 901)
164901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namdyn_adv in reference namelist', lwp )
165      REWIND( numnam_ice_cfg )         ! Namelist namdyn_adv in configuration namelist : Ice dynamics
166      READ  ( numnam_ice_cfg, namdyn_adv, IOSTAT = ios, ERR = 902 )
167902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namdyn_adv in configuration namelist', lwp )
168      IF(lwm) WRITE( numoni, namdyn_adv )
169      !
170      IF(lwp) THEN                     ! control print
171         WRITE(numout,*)
172         WRITE(numout,*) 'ice_dyn_adv_init: ice parameters for ice dynamics '
173         WRITE(numout,*) '~~~~~~~~~~~~~~~~'
174         WRITE(numout,*) '   Namelist namdyn_adv:'
175         WRITE(numout,*) '      type of advection scheme (Prather)             ln_adv_Pra = ', ln_adv_Pra 
176         WRITE(numout,*) '      type of advection scheme (Ulimate-Macho)       ln_adv_UMx = ', ln_adv_UMx 
177         WRITE(numout,*) '         order of the Ultimate-Macho scheme          nn_UMx     = ', nn_UMx
178      ENDIF
179      !
180      !                             !== set the choice of ice advection ==!
181      ioptio = 0 
182      IF( ln_adv_Pra ) THEN   ;   ioptio = ioptio + 1   ;   nice_adv = np_advPRA    ;   ENDIF
183      IF( ln_adv_UMx ) THEN   ;   ioptio = ioptio + 1   ;   nice_adv = np_advUMx    ;   ENDIF
184      IF( ioptio /= 1 )   CALL ctl_stop( 'ice_dyn_adv_init: choose one and only one ice adv. scheme (ln_adv_Pra or ln_adv_UMx)' )
185      !
186      IF( ln_adv_Pra )   CALL adv_pra_init  !* read or initialize all required files
187      !
188   END SUBROUTINE ice_dyn_adv_init
189
190#else
191   !!----------------------------------------------------------------------
192   !!   Default option         Empty Module           NO SI3 sea-ice model
193   !!----------------------------------------------------------------------
194#endif
195
196   !!======================================================================
197END MODULE icedyn_adv
198
Note: See TracBrowser for help on using the repository browser.