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.F90 in branches/dev_001_SBC/NEMO/LIM_SRC – NEMO

source: branches/dev_001_SBC/NEMO/LIM_SRC/limdmp.F90 @ 881

Last change on this file since 881 was 881, checked in by ctlod, 16 years ago

dev_001_SBC: Step I: change cpp ket name key_ice_lim into key_lim2 & change names inside modules with extension _2, see ticket: #110

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