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 @ 1465

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

supress ice_oce module, see ticket:448

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