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

source: trunk/NEMOGCM/NEMO/LIM_SRC_3/limdyn.F90 @ 7698

Last change on this file since 7698 was 7698, checked in by mocavero, 7 years ago

update trunk with OpenMP parallelization

  • Property svn:keywords set to Id
File size: 8.2 KB
RevLine 
[825]1MODULE limdyn
2   !!======================================================================
3   !!                     ***  MODULE  limdyn  ***
4   !!   Sea-Ice dynamics : 
5   !!======================================================================
[2715]6   !! history :  1.0  ! 2002-08  (C. Ethe, G. Madec)  original VP code
7   !!            3.0  ! 2007-03  (MA Morales Maqueda, S. Bouillon, M. Vancoppenolle)  LIM3: EVP-Cgrid
[5123]8   !!            3.5  ! 2011-02  (G. Madec) dynamical allocation
[2528]9   !!----------------------------------------------------------------------
[825]10#if defined key_lim3
11   !!----------------------------------------------------------------------
[834]12   !!   'key_lim3' :                                 LIM3 sea-ice model
[825]13   !!----------------------------------------------------------------------
14   !!    lim_dyn      : computes ice velocities
15   !!    lim_dyn_init : initialization and namelist read
16   !!----------------------------------------------------------------------
[4161]17   USE phycst           ! physical constants
18   USE dom_oce          ! ocean space and time domain
19   USE sbc_ice          ! Surface boundary condition: ice   fields
20   USE ice              ! LIM-3 variables
21   USE limrhg           ! LIM-3 rheology
22   USE lbclnk           ! lateral boundary conditions - MPP exchanges
23   USE lib_mpp          ! MPP library
24   USE wrk_nemo         ! work arrays
25   USE in_out_manager   ! I/O manager
26   USE lib_fortran      ! glob_sum
[7646]27   USE timing           ! Timing
28   USE limcons          ! conservation tests
29   USE limctl           ! control prints
[5123]30   USE limvar
[825]31
32   IMPLICIT NONE
33   PRIVATE
34
[7646]35   PUBLIC   lim_dyn        ! routine called by sbcice_lim.F90
36   PUBLIC   lim_dyn_init   ! routine called by sbcice_lim.F90
[825]37
[868]38   !! * Substitutions
39#  include "vectopt_loop_substitute.h90"
[825]40   !!----------------------------------------------------------------------
[4161]41   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
[1156]42   !! $Id$
[2528]43   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[825]44   !!----------------------------------------------------------------------
45CONTAINS
46
[921]47   SUBROUTINE lim_dyn( kt )
[825]48      !!-------------------------------------------------------------------
49      !!               ***  ROUTINE lim_dyn  ***
50      !!               
[7646]51      !! ** Purpose :   compute ice velocity
[825]52      !!               
53      !! ** Method  :
54      !!
55      !! ** Action  : - Initialisation
56      !!              - Call of the dynamic routine for each hemisphere
57      !!------------------------------------------------------------------------------------
[921]58      INTEGER, INTENT(in) ::   kt     ! number of iteration
[2528]59      !!
[7698]60      INTEGER  :: ji, jj, jl, jk ! dummy loop indices
[4688]61      REAL(wp) :: zvi_b, zsmv_b, zei_b, zfs_b, zfw_b, zft_b 
[4161]62     !!---------------------------------------------------------------------
[825]63
[4161]64      IF( nn_timing == 1 )  CALL timing_start('limdyn')
65
[7646]66      CALL lim_var_agg(1)                      ! aggregate ice categories
67      !
68      ! conservation test
69      IF( ln_limdiachk ) CALL lim_cons_hsm(0, 'limdyn', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b)
70     
[7698]71!$OMP PARALLEL DO schedule(static) private(jj,ji)
72      DO jj = 1, jpj
73         DO ji = 1, jpi
74            ! ice velocities before rheology
75            u_ice_b(ji,jj) = u_ice(ji,jj) * umask(ji,jj,1)
76            v_ice_b(ji,jj) = v_ice(ji,jj) * vmask(ji,jj,1)
[7646]77     
[7698]78            ! Landfast ice parameterization: define max bottom friction
79            tau_icebfr(ji,jj) = 0._wp
80         END DO
81      END DO
[7646]82      IF( ln_landfast ) THEN
[863]83         DO jl = 1, jpl
[7698]84!$OMP PARALLEL DO schedule(static) private(jj,ji)
85            DO jj = 1, jpj
86               DO ji = 1, jpi
87                  IF( ht_i(ji,jj,jl) > ht_n(ji,jj) * rn_gamma )  tau_icebfr(ji,jj) = tau_icebfr(ji,jj) + a_i(ji,jj,jl) * rn_icebfr
88               END DO
89            END DO
[863]90         END DO
[825]91      ENDIF
[7646]92     
93      ! Rheology (ice dynamics)
94      ! ========     
95      CALL lim_rhg
[2528]96      !
[7646]97      ! conservation test
98      IF( ln_limdiachk ) CALL lim_cons_hsm(1, 'limdyn', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b)
99
100      ! Control prints
101      IF( ln_ctl )       CALL lim_prt3D( 'limdyn' )
[2715]102      !
[4161]103      IF( nn_timing == 1 )  CALL timing_stop('limdyn')
104
[825]105   END SUBROUTINE lim_dyn
106
[2528]107
[921]108   SUBROUTINE lim_dyn_init
[825]109      !!-------------------------------------------------------------------
110      !!                  ***  ROUTINE lim_dyn_init  ***
111      !!
112      !! ** Purpose : Physical constants and parameters linked to the ice
113      !!      dynamics
114      !!
115      !! ** Method  :  Read the namicedyn namelist and check the ice-dynamic
116      !!       parameter values called at the first timestep (nit000)
117      !!
118      !! ** input   :   Namelist namicedyn
119      !!-------------------------------------------------------------------
[4147]120      INTEGER  ::   ios                 ! Local integer output status for namelist read
[7646]121      NAMELIST/namicedyn/ nn_limadv, nn_limadv_ord,  &
122         &                nn_icestr, ln_icestr_bvf, rn_pe_rdg, rn_pstar, rn_crhg, rn_cio, rn_creepl, rn_ecc, &
123         &                nn_nevp, rn_relast, ln_landfast, rn_gamma, rn_icebfr, rn_lfrelax
[825]124      !!-------------------------------------------------------------------
125
[4147]126      REWIND( numnam_ice_ref )              ! Namelist namicedyn in reference namelist : Ice dynamics
127      READ  ( numnam_ice_ref, namicedyn, IOSTAT = ios, ERR = 901)
128901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicedyn in reference namelist', lwp )
129
130      REWIND( numnam_ice_cfg )              ! Namelist namicedyn in configuration namelist : Ice dynamics
131      READ  ( numnam_ice_cfg, namicedyn, IOSTAT = ios, ERR = 902 )
132902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicedyn in configuration namelist', lwp )
[4624]133      IF(lwm) WRITE ( numoni, namicedyn )
[2528]134     
135      IF(lwp) THEN                        ! control print
[825]136         WRITE(numout,*)
137         WRITE(numout,*) 'lim_dyn_init : ice parameters for ice dynamics '
138         WRITE(numout,*) '~~~~~~~~~~~~'
[7646]139         ! limtrp
140         WRITE(numout,*)'    choose the advection scheme (-1=Prather, 0=Ulimate-Macho)   nn_limadv     = ', nn_limadv 
141         WRITE(numout,*)'    choose the order of the scheme (if ultimate)                nn_limadv_ord = ', nn_limadv_ord 
142         ! limrhg
143         WRITE(numout,*)'    ice strength parameterization (0=Hibler 1=Rothrock)         nn_icestr     = ', nn_icestr 
144         WRITE(numout,*)'    Including brine volume in ice strength comp.                ln_icestr_bvf = ', ln_icestr_bvf
145         WRITE(numout,*)'    Ratio of ridging work to PotEner change in ridging          rn_pe_rdg     = ', rn_pe_rdg 
146         WRITE(numout,*) '   drag coefficient for oceanic stress                         rn_cio        = ', rn_cio
147         WRITE(numout,*) '   first bulk-rheology parameter                               rn_pstar      = ', rn_pstar
148         WRITE(numout,*) '   second bulk-rhelogy parameter                               rn_crhg       = ', rn_crhg
149         WRITE(numout,*) '   creep limit                                                 rn_creepl     = ', rn_creepl
150         WRITE(numout,*) '   eccentricity of the elliptical yield curve                  rn_ecc        = ', rn_ecc
151         WRITE(numout,*) '   number of iterations for subcycling                         nn_nevp       = ', nn_nevp
152         WRITE(numout,*) '   ratio of elastic timescale over ice time step               rn_relast     = ', rn_relast
153         WRITE(numout,*) '   Landfast: param (T or F)                                    ln_landfast   = ', ln_landfast
154         WRITE(numout,*) '   Landfast: fraction of ocean depth that ice must reach       rn_gamma      = ', rn_gamma
155         WRITE(numout,*) '   Landfast: maximum bottom stress per unit area of contact    rn_icebfr     = ', rn_icebfr
156         WRITE(numout,*) '   Landfast: relax time scale (s-1) to reach static friction   rn_lfrelax    = ', rn_lfrelax
[825]157      ENDIF
[2528]158      !
[825]159   END SUBROUTINE lim_dyn_init
160
161#else
162   !!----------------------------------------------------------------------
163   !!   Default option          Empty module           NO LIM sea-ice model
164   !!----------------------------------------------------------------------
165CONTAINS
166   SUBROUTINE lim_dyn         ! Empty routine
167   END SUBROUTINE lim_dyn
168#endif 
169
170   !!======================================================================
171END MODULE limdyn
Note: See TracBrowser for help on using the repository browser.