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.
limdmp_2.F90 in trunk/NEMO/LIM_SRC_2 – NEMO

source: trunk/NEMO/LIM_SRC_2/limdmp_2.F90 @ 1850

Last change on this file since 1850 was 1715, checked in by smasson, 15 years ago

move daymod public variables in dom_oce, see ticket:590

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 7.6 KB
RevLine 
[821]1MODULE limdmp_2
[420]2   !!======================================================================
[821]3   !!                       ***  MODULE limdmp_2   ***
[420]4   !!  Ice model : restoring Ice thickness and Fraction leads
5   !!======================================================================
[508]6   !! History :   2.0  !  04-04 (S. Theetten) Original code
[420]7   !!----------------------------------------------------------------------
[821]8#if defined key_lim2   &&   defined key_tradmp
[420]9   !!----------------------------------------------------------------------
[821]10   !!   'key_lim2'  AND                               LIM 2.0 sea-ice model
[508]11   !!   'key_tradmp'                                                Damping
12   !!----------------------------------------------------------------------
13   !!----------------------------------------------------------------------
[821]14   !!   lim_dmp_2      : ice model damping
[420]15   !!----------------------------------------------------------------------
16   USE in_out_manager  ! I/O manager
[508]17   USE phycst          ! physical constants
[821]18   USE ice_2
[420]19   USE tradmp
20   USE dom_oce
21   USE oce
[508]22   USE iom
[420]23   
24   IMPLICIT NONE
25   PRIVATE
26
[821]27   PUBLIC   lim_dmp_2     ! called by ice_step_2
[420]28   
[508]29   INTEGER                        ::   nice1, nice2,  &  ! first and second record used
30      &                                inumice_dmp       ! logical unit for ice variables (damping)
31   REAL(wp), DIMENSION(jpi,jpj)   ::   hicif_dta  ,   &  ! ice thickness at a given time
32      &                                frld_dta          ! fraction lead at a given time
33   REAL(wp), DIMENSION(jpi,jpj,2) ::   hicif_data ,   &  ! ice thickness data at two consecutive times
34      &                                frld_data         ! fraction lead data at two consecutive times
[420]35
36   !! * Substitution
37#  include "vectopt_loop_substitute.h90"
38   !!----------------------------------------------------------------------
[508]39   !!   LIM 2.0 , UCL-LOCEAN-IPSL  (2006)
[1156]40   !! $Id$
[508]41   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
[420]42   !!----------------------------------------------------------------------
43
44CONTAINS
45
[821]46   SUBROUTINE lim_dmp_2(kt)
[420]47      !!-------------------------------------------------------------------
[821]48      !!                   ***  ROUTINE lim_dmp_2 ***
[420]49      !!
50      !! ** purpose : ice model damping : restoring ice thickness and
51      !!              fraction leads
52      !!
53      !! ** method  : the key_tradmp must be used to compute resto(:,:) coef.
54      !!---------------------------------------------------------------------
[508]55      INTEGER, INTENT(in) ::   kt     ! ocean time-step
56      !
57      INTEGER             ::   ji, jj         ! dummy loop indices
[420]58      !!---------------------------------------------------------------------
[508]59      !
[821]60      CALL dta_lim_2( kt )
[420]61
62      DO jj = 2, jpjm1
63         DO ji = fs_2, fs_jpim1   ! vector opt.
[508]64            hicif(ji,jj) = hicif(ji,jj) - rdt_ice * resto(ji,jj,1) * ( hicif(ji,jj) - hicif_dta(ji,jj) )
65            frld(ji,jj)  = frld (ji,jj) - rdt_ice * resto(ji,jj,1) * ( frld(ji,jj)  - frld_dta (ji,jj) ) 
66         END DO
67      END DO
68      !
[821]69   END SUBROUTINE lim_dmp_2
[420]70
71
[821]72   SUBROUTINE dta_lim_2( kt ) 
[420]73      !!----------------------------------------------------------------------
[821]74      !!                   ***  ROUTINE dta_lim_2  ***
[420]75      !!
76      !! ** Purpose :   Reads monthly ice thickness and fraction lead  data
77      !!
78      !! ** Method  :   Read on unit numicedt the interpolated ice variable
79      !!      onto the model grid.
80      !!      Data begin at january.
81      !!      The value is centered at the middle of month.
82      !!      In the opa model, kt=1 agree with january 1.
83      !!      At each time step, a linear interpolation is applied between
84      !!      two monthly values.
85      !!     
86      !! ** Action  :   define hicif_dta and frld_dta arrays at time-step kt
87      !!----------------------------------------------------------------------
[508]88      INTEGER, INTENT(in) ::   kt     ! ocean time-step
89      !
90      INTEGER  ::   imois, iman, i15          ! temporary integers
91      REAL(wp) ::   zxy
[420]92      !!----------------------------------------------------------------------
93
94      ! 0. Initialization
95      ! -----------------
[508]96      iman  = INT( raamo )
97!!! better but change the results     i15 = INT( 2*FLOAT( nday ) / ( FLOAT( nobis(nmonth) ) + 0.5 ) )
[420]98      i15   = nday / 16
99      imois = nmonth + i15 - 1
[508]100      IF( imois == 0 ) imois = iman
101     
102      ! 1. First call kt=nit000: Initialization and Open
[420]103      ! -----------------------
104      IF( kt == nit000 ) THEN
105         nice1 = 0
106         IF(lwp) WRITE(numout,*)
107         IF(lwp) WRITE(numout,*) 'dtalim : Ice thickness and lead fraction  monthly fields'
108         IF(lwp) WRITE(numout,*) '~~~~~~'
109         IF(lwp) WRITE(numout,*) '             NetCDF FORMAT'
110         IF(lwp) WRITE(numout,*)
111         ! open file
[508]112         CALL iom_open( 'ice_damping_ATL4.nc', inumice_dmp )
[420]113      ENDIF
114
115
116      ! 2. Read monthly file
[508]117      ! --------------------
[420]118      IF( ( kt == nit000 ) .OR. imois /= nice1 ) THEN
[508]119         !
[420]120         ! Calendar computation
121         nice1 = imois        ! first file record used
122         nice2 = nice1 + 1    ! last  file record used
123         nice1 = MOD( nice1, iman )
[508]124         nice2 = MOD( nice2, iman )
[420]125         IF( nice1 == 0 )   nice1 = iman
126         IF( nice2 == 0 )   nice2 = iman
127         IF(lwp) WRITE(numout,*) 'first record file used nice1 ', nice1
128         IF(lwp) WRITE(numout,*) 'last  record file used nice2 ', nice2
129         
130         ! Read monthly ice thickness Levitus
[508]131         CALL iom_get( inumice_dmp, jpdom_data, 'iicethic', hicif_data(:,:,1), nice1 ) 
132         CALL iom_get( inumice_dmp, jpdom_data, 'iicethic', hicif_data(:,:,2), nice2 ) 
[420]133         
134         ! Read monthly ice thickness Levitus
[508]135         CALL iom_get( inumice_dmp, jpdom_data, 'ileadfra', frld_data(:,:,1), nice1 ) 
136         CALL iom_get( inumice_dmp, jpdom_data, 'ileadfra', frld_data(:,:,2), nice2 ) 
[420]137         
138         ! The fraction lead read in the file is in fact the
139         ! ice concentration which is 1 - the fraction lead
140         frld_data = 1 - frld_data         
141         
142         IF(lwp) THEN
[508]143            WRITE(numout,*)
[420]144            WRITE(numout,*) ' Ice thickness month ', nice1,' and ', nice2
145            WRITE(numout,*)
146            WRITE(numout,*) ' Ice thickness month = ', nice1
147            CALL prihre( hicif_data(1,1,1), jpi, jpj, 1, jpi, 20, 1, jpj, 20, 1., numout )
148            WRITE(numout,*)
149            WRITE(numout,*) ' Fraction lead months ', nice1,' and ', nice2
150            WRITE(numout,*)
151            WRITE(numout,*) ' Fraction lead month = ', nice1
152            CALL prihre( frld_data(1,1,1), jpi, jpj, 1, jpi, 20, 1, jpj, 20, 1., numout )
153         ENDIF
154
[674]155         CALL FLUSH(numout)
156
[420]157      ENDIF
[674]158       
159      ! 3. At every time step compute ice thickness and fraction lead data
160      ! ------------------------------------------------------------------
161      zxy = FLOAT( nday + 15 - 30 * i15 ) / 30.
162      hicif_dta(:,:) = (1.-zxy) * hicif_data(:,:,1) + zxy * hicif_data(:,:,2)
163      frld_dta (:,:) = (1.-zxy) * frld_data (:,:,1) + zxy * frld_data (:,:,2)
164
[508]165      IF( kt == nitend )   CALL iom_close( inumice_dmp )
166      !
[821]167   END SUBROUTINE dta_lim_2
[420]168
169#else
170   !!----------------------------------------------------------------------
171   !!   Default option         Empty Module                  No ice damping
172   !!----------------------------------------------------------------------
173CONTAINS
[821]174   SUBROUTINE lim_dmp_2( kt )        ! Dummy routine
175      WRITE(*,*) 'lim_dmp_2: You should not see this print! error? ', kt
176   END SUBROUTINE lim_dmp_2
[420]177#endif
178
179   !!======================================================================
[821]180END MODULE limdmp_2
Note: See TracBrowser for help on using the repository browser.