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 branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/LIM_SRC_2 – NEMO

source: branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/LIM_SRC_2/limdmp_2.F90 @ 1855

Last change on this file since 1855 was 1855, checked in by gm, 14 years ago

ticket:#665 style change only, with the suppression of thd_ice_2 (merged in ice_2)

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