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_rhg.F90 in NEMO/branches/2020/SI3_vp_rheology/src/ICE – NEMO

source: NEMO/branches/2020/SI3_vp_rheology/src/ICE/icedyn_rhg.F90 @ 13920

Last change on this file since 13920 was 13920, checked in by vancop, 4 years ago

commit everything but VP

  • Property svn:keywords set to Id
File size: 9.9 KB
RevLine 
[8586]1MODULE icedyn_rhg
2   !!======================================================================
3   !!                     ***  MODULE  icedyn_rhg  ***
4   !!   Sea-Ice dynamics : master routine for rheology
5   !!======================================================================
[9604]6   !! history :  4.0  !  2018     (C. Rousset)      Original code
[8586]7   !!----------------------------------------------------------------------
[9570]8#if defined key_si3
[8586]9   !!----------------------------------------------------------------------
[9570]10   !!   'key_si3'                                       SI3 sea-ice model
[8586]11   !!----------------------------------------------------------------------
12   !!    ice_dyn_rhg      : computes ice velocities
13   !!    ice_dyn_rhg_init : initialization and namelist read
14   !!----------------------------------------------------------------------
15   USE phycst         ! physical constants
16   USE dom_oce        ! ocean space and time domain
17   USE ice            ! sea-ice: variables
18   USE icedyn_rhg_evp ! sea-ice: EVP rheology
[13920]19   USE icedyn_rhg_vp  ! sea-ice: VP rheology
[8586]20   USE icectl         ! sea-ice: control prints
21   !
22   USE in_out_manager ! I/O manager
23   USE lib_mpp        ! MPP library
24   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero)
25   USE timing         ! Timing
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   ice_dyn_rhg        ! called by icestp.F90
31   PUBLIC   ice_dyn_rhg_init   ! called by icestp.F90
32
33   INTEGER ::              nice_rhg   ! choice of the type of rheology
34   !                                        ! associated indices:
35   INTEGER, PARAMETER ::   np_rhgEVP = 1   ! EVP rheology
36!! INTEGER, PARAMETER ::   np_rhgEAP = 2   ! EAP rheology
[13920]37   INTEGER, PARAMETER ::   np_rhgVP  = 3   ! VP rheology
[8586]38
39   ! ** namelist (namrhg) **
40   LOGICAL ::   ln_rhg_EVP       ! EVP rheology
[13920]41   LOGICAL ::   ln_rhg_VP        ! EVP rheology
[8586]42   !
43   !!----------------------------------------------------------------------
[9598]44   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
[10069]45   !! $Id$
[10413]46   !! Software governed by the CeCILL licence     (./LICENSE)
[8586]47   !!----------------------------------------------------------------------
48CONTAINS
49
[12377]50   SUBROUTINE ice_dyn_rhg( kt, Kmm )
[8586]51      !!-------------------------------------------------------------------
52      !!               ***  ROUTINE ice_dyn_rhg  ***
53      !!               
54      !! ** Purpose :   compute ice velocity
55      !!
56      !! ** Action  : comupte - ice velocity (u_ice, v_ice)
57      !!                      - 3 components of the stress tensor (stress1_i, stress2_i, stress12_i)
58      !!                      - shear, divergence and delta (shear_i, divu_i, delta_i)
59      !!--------------------------------------------------------------------
60      INTEGER, INTENT(in) ::   kt     ! ice time step
[12377]61      INTEGER, INTENT(in) ::   Kmm    ! ocean time level index
[8586]62      !!--------------------------------------------------------------------
63      ! controls
[9124]64      IF( ln_timing    )   CALL timing_start('icedyn_rhg')                                                             ! timing
65      IF( ln_icediachk )   CALL ice_cons_hsm(0, 'icedyn_rhg', rdiag_v, rdiag_s, rdiag_t, rdiag_fv, rdiag_fs, rdiag_ft) ! conservation
[11536]66      IF( ln_icediachk )   CALL ice_cons2D  (0, 'icedyn_rhg',  diag_v,  diag_s,  diag_t,  diag_fv,  diag_fs,  diag_ft) ! conservation
[8586]67      !
68      IF( kt == nit000 .AND. lwp ) THEN
69         WRITE(numout,*)
70         WRITE(numout,*)'ice_dyn_rhg: sea-ice rheology'
71         WRITE(numout,*)'~~~~~~~~~~~'
72      ENDIF
[10911]73      !
74      !--------------!
75      !== Rheology ==!
76      !--------------!   
[8586]77      SELECT CASE( nice_rhg )
78      !                                !------------------------!
79      CASE( np_rhgEVP )                ! Elasto-Viscous-Plastic !
80         !                             !------------------------!
[12377]81         CALL ice_dyn_rhg_evp( kt, Kmm, stress1_i, stress2_i, stress12_i, shear_i, divu_i, delta_i )
[13920]82         !       
83         !                             !---------------------------------------------!
84      CASE( np_rhgVP  )                ! Viscous-Plastic rheology                    !
85         !                             !---------------------------------------------!
86         CALL ice_dyn_rhg_vp ( kt, shear_i, divu_i, delta_i )
[8586]87      END SELECT
88      !
89      IF( lrst_ice ) THEN                       !* write EVP fields in the restart file
90         IF( ln_rhg_EVP )   CALL rhg_evp_rst( 'WRITE', kt )
[13920]91         ! MV note: no restart needed for VP as there is no time equation for stress tensor
[8586]92      ENDIF
93      !
94      ! controls
[12377]95      IF( sn_cfctl%l_prtctl ) &
96         &                 CALL ice_prt3D   ('icedyn_rhg')                                                             ! prints
[9124]97      IF( ln_icediachk )   CALL ice_cons_hsm(1, 'icedyn_rhg', rdiag_v, rdiag_s, rdiag_t, rdiag_fv, rdiag_fs, rdiag_ft) ! conservation
[11536]98      IF( ln_icediachk )   CALL ice_cons2D  (1, 'icedyn_rhg',  diag_v,  diag_s,  diag_t,  diag_fv,  diag_fs,  diag_ft) ! conservation
[9124]99      IF( ln_timing    )   CALL timing_stop ('icedyn_rhg')                                                             ! timing
[8586]100      !
101   END SUBROUTINE ice_dyn_rhg
102
[9124]103
[8586]104   SUBROUTINE ice_dyn_rhg_init
105      !!-------------------------------------------------------------------
106      !!                  ***  ROUTINE ice_dyn_rhg_init  ***
107      !!
108      !! ** Purpose : Physical constants and parameters linked to the ice
109      !!      dynamics
110      !!
111      !! ** Method  :  Read the namdyn_rhg namelist and check the ice-dynamic
112      !!       parameter values called at the first timestep (nit000)
113      !!
114      !! ** input   :   Namelist namdyn_rhg
115      !!-------------------------------------------------------------------
116      INTEGER ::   ios, ioptio   ! Local integer output status for namelist read
117      !!
[13920]118      NAMELIST/namdyn_rhg/  ln_rhg_EVP, ln_aEVP, rn_creepl, rn_ecc , nn_nevp, rn_relast, nn_rhg_chkcvg,   &    !-- evp
119    &                       ln_rhg_VP, nn_nout_vp, nn_ninn_vp, ln_zebra_vp, rn_relaxu_vp, rn_relaxv_vp, rn_uerr_max_vp, rn_uerr_min_vp, nn_cvgchk_vp  !-- vp
[8586]120      !!-------------------------------------------------------------------
121      !
122      READ  ( numnam_ice_ref, namdyn_rhg, IOSTAT = ios, ERR = 901)
[11536]123901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_rhg in reference namelist' )
[8586]124      READ  ( numnam_ice_cfg, namdyn_rhg, IOSTAT = ios, ERR = 902 )
[11536]125902   IF( ios >  0 ) CALL ctl_nam ( ios , 'namdyn_rhg in configuration namelist' )
[8586]126      IF(lwm) WRITE ( numoni, namdyn_rhg )
127      !
128      IF(lwp) THEN                     ! control print
129         WRITE(numout,*)
130         WRITE(numout,*) 'ice_dyn_rhg_init: ice parameters for ice dynamics '
131         WRITE(numout,*) '~~~~~~~~~~~~~~~'
[9169]132         WRITE(numout,*) '   Namelist : namdyn_rhg:'
[13472]133         WRITE(numout,*) '      rheology EVP (icedyn_rhg_evp)                        ln_rhg_EVP    = ', ln_rhg_EVP
134         WRITE(numout,*) '         use adaptive EVP (aEVP)                           ln_aEVP       = ', ln_aEVP
[13920]135         WRITE(numout,*) '         creep limit                                       rn_creepl     = ', rn_creepl ! also used by vp
136         WRITE(numout,*) '         eccentricity of the elliptical yield curve        rn_ecc        = ', rn_ecc    ! also used by vp
[13472]137         WRITE(numout,*) '         number of iterations for subcycling               nn_nevp       = ', nn_nevp
138         WRITE(numout,*) '         ratio of elastic timescale over ice time step     rn_relast     = ', rn_relast
[13920]139         WRITE(numout,*) '      check convergence of rheology                        nn_rhg_chkcvg = ', nn_rhg_chkcvg ! maybe duplicates nn_cvgchk_vp ?
140         WRITE(numout,*) '      rheology VP     (icedyn_rhg_VP)                      ln_rhg_VP     = ', ln_rhg_VP
141         WRITE(numout,*) '         number of outer iterations                        nn_nout_vp    = ', nn_nout_vp
142         WRITE(numout,*) '         number of inner iterations                        nn_ninn_vp    = ', nn_ninn_vp
143         WRITE(numout,*) '         activate zebra solver                             ln_zebra_vp   = ', ln_zebra_vp
144         WRITE(numout,*) '         relaxation factor for u                           rn_relaxu_vp  = ', rn_relaxu_vp
145         WRITE(numout,*) '         relaxation factor for v                           rn_relaxv_vp  = ', rn_relaxv_vp
146         WRITE(numout,*) '         maximum error on velocity                         rn_uerr_max_vp = ', rn_uerr_max_vp
147         WRITE(numout,*) '         velocity to decide convergence                    rn_uerr_min_vp = ', rn_uerr_min_vp
148         WRITE(numout,*) '         iteration step for convergence check              nn_cvgchk_vp   = ', nn_cvgchk_vp
[13472]149         IF    ( nn_rhg_chkcvg == 0 ) THEN   ;   WRITE(numout,*) '         no check'
150         ELSEIF( nn_rhg_chkcvg == 1 ) THEN   ;   WRITE(numout,*) '         check cvg at the main time step'
151         ELSEIF( nn_rhg_chkcvg == 2 ) THEN   ;   WRITE(numout,*) '         check cvg at both main and rheology time steps'
152         ENDIF
[8586]153      ENDIF
154      !
155      !                             !== set the choice of ice advection ==!
156      ioptio = 0 
157      IF( ln_rhg_EVP ) THEN   ;   ioptio = ioptio + 1   ;   nice_rhg = np_rhgEVP    ;   ENDIF
158!!    IF( ln_rhg_EAP ) THEN   ;   ioptio = ioptio + 1   ;   nice_rhg = np_rhgEAP    ;   ENDIF
[13920]159      IF( ln_rhg_VP  ) THEN   ;   ioptio = ioptio + 1   ;   nice_rhg = np_rhgVP     ;   ENDIF
[8586]160      IF( ioptio /= 1 )   CALL ctl_stop( 'ice_dyn_rhg_init: choose one and only one ice rheology' )
161      !
[8813]162      IF( ln_rhg_EVP  )   CALL rhg_evp_rst( 'READ' )  !* read or initialize all required files
[13920]163      ! no restart for VP as there is no explicit time dependency in the equation
[8586]164      !
165   END SUBROUTINE ice_dyn_rhg_init
166
167#else
168   !!----------------------------------------------------------------------
[9570]169   !!   Default option         Empty module           NO SI3 sea-ice model
[8586]170   !!----------------------------------------------------------------------
171#endif 
172
173   !!======================================================================
174END MODULE icedyn_rhg
Note: See TracBrowser for help on using the repository browser.