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.
sbcice_cice.F90 in branches/2012/dev_3352_UKMO8_CICE/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2012/dev_3352_UKMO8_CICE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90 @ 3480

Last change on this file since 3480 was 3480, checked in by charris, 12 years ago

#953 Removing salinity dependence of freezing point for the moment (will be implemented more completely in NEMO3.6).
Reversed r3356 of /branches/2012/dev_3352_UKMO8_CICE/NEMOGCM

File size: 38.1 KB
Line 
1MODULE sbcice_cice
2   !!======================================================================
3   !!                       ***  MODULE  sbcice_cice  ***
4   !! To couple with sea ice model CICE (LANL)
5   !!=====================================================================
6#if defined key_cice
7   !!----------------------------------------------------------------------
8   !!   'key_cice' :                                     CICE sea-ice model
9   !!----------------------------------------------------------------------
10   !!   sbc_ice_cice  : sea-ice model time-stepping and update ocean sbc over ice-covered area
11   !!   
12   !!   
13   !!----------------------------------------------------------------------
14   USE oce             ! ocean dynamics and tracers
15   USE dom_oce         ! ocean space and time domain
16   USE domvvl
17   USE phycst, only : rcp, rau0
18   USE in_out_manager  ! I/O manager
19   USE lib_mpp         ! distributed memory computing library
20   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
21   USE wrk_nemo        ! work arrays
22   USE timing          ! Timing
23   USE daymod          ! calendar
24   USE fldread         ! read input fields
25
26   USE sbc_oce         ! Surface boundary condition: ocean fields
27   USE sbc_ice         ! Surface boundary condition: ice   fields
28   USE sbcblk_core     ! Surface boundary condition: CORE bulk
29   USE sbccpl
30
31   USE ice_kinds_mod
32   USE ice_blocks
33   USE ice_domain
34   USE ice_domain_size
35   USE ice_boundary
36   USE ice_constants
37   USE ice_gather_scatter
38   USE ice_calendar, only: dt
39   USE ice_state, only: aice,aicen,uvel,vvel,vsnon,vicen
40   USE ice_flux, only: strax,stray,strocnx,strocny,frain,fsnow,  &
41                sst,sss,uocn,vocn,ss_tltx,ss_tlty,fsalt_gbm,     &
42                fresh_gbm,fhocn_gbm,fswthru_gbm,frzmlt,          &
43                flatn_f,fsurfn_f,fcondtopn_f,                    &
44                uatm,vatm,wind,fsw,flw,Tair,potT,Qa,rhoa,zlvl,   &
45                swvdr,swvdf,swidr,swidf
46   USE ice_forcing, only: frcvdr,frcvdf,frcidr,frcidf
47   USE ice_atmo, only: calc_strair
48   USE ice_therm_vertical, only: calc_Tsfc
49
50   USE CICE_InitMod
51   USE CICE_RunMod
52   USE CICE_FinalMod
53
54   IMPLICIT NONE
55   PRIVATE
56
57   !! * Routine accessibility
58   PUBLIC cice_sbc_init   ! routine called by sbc_init
59   PUBLIC cice_sbc_final  ! routine called by sbc_final
60   PUBLIC sbc_ice_cice    ! routine called by sbc
61
62   INTEGER , PARAMETER ::   ji_off = INT ( (jpiglo - nx_global) / 2 )
63   INTEGER , PARAMETER ::   jj_off = INT ( (jpjglo - ny_global) / 2 )
64
65   INTEGER , PARAMETER ::   jpfld   = 13   ! maximum number of files to read
66   INTEGER , PARAMETER ::   jp_snow = 1    ! index of snow file
67   INTEGER , PARAMETER ::   jp_rain = 2    ! index of rain file
68   INTEGER , PARAMETER ::   jp_sblm = 3    ! index of sublimation file
69   INTEGER , PARAMETER ::   jp_top1 = 4    ! index of category 1 topmelt file
70   INTEGER , PARAMETER ::   jp_top2 = 5    ! index of category 2 topmelt file
71   INTEGER , PARAMETER ::   jp_top3 = 6    ! index of category 3 topmelt file
72   INTEGER , PARAMETER ::   jp_top4 = 7    ! index of category 4 topmelt file
73   INTEGER , PARAMETER ::   jp_top5 = 8    ! index of category 5 topmelt file
74   INTEGER , PARAMETER ::   jp_bot1 = 9    ! index of category 1 botmelt file
75   INTEGER , PARAMETER ::   jp_bot2 = 10   ! index of category 2 botmelt file
76   INTEGER , PARAMETER ::   jp_bot3 = 11   ! index of category 3 botmelt file
77   INTEGER , PARAMETER ::   jp_bot4 = 12   ! index of category 4 botmelt file
78   INTEGER , PARAMETER ::   jp_bot5 = 13   ! index of category 5 botmelt file
79   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf    ! structure of input fields (file informations, fields read)
80
81   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:), PRIVATE ::   png     ! local array used in sbc_cice_ice
82
83   !! * Substitutions
84#  include "domzgr_substitute.h90"
85
86CONTAINS
87
88   INTEGER FUNCTION sbc_ice_cice_alloc()
89      !!----------------------------------------------------------------------
90      !!                ***  FUNCTION sbc_ice_cice_alloc  ***
91      !!----------------------------------------------------------------------
92      ALLOCATE( png(jpi,jpj,jpnij), STAT=sbc_ice_cice_alloc )
93      IF( lk_mpp                 )   CALL mpp_sum ( sbc_ice_cice_alloc )
94      IF( sbc_ice_cice_alloc > 0 )   CALL ctl_warn('sbc_ice_cice_alloc: allocation of arrays failed.')
95   END FUNCTION sbc_ice_cice_alloc
96
97   SUBROUTINE sbc_ice_cice( kt, nsbc )
98      !!---------------------------------------------------------------------
99      !!                  ***  ROUTINE sbc_ice_cice  ***
100      !!                   
101      !! ** Purpose :   update the ocean surface boundary condition via the
102      !!                CICE Sea Ice Model time stepping
103      !!
104      !! ** Method  : - Get any extra forcing fields for CICE 
105      !!              - Prepare forcing fields
106      !!              - CICE model time stepping
107      !!              - call the routine that computes mass and
108      !!                heat fluxes at the ice/ocean interface
109      !!
110      !! ** Action  : - time evolution of the CICE sea-ice model
111      !!              - update all sbc variables below sea-ice:
112      !!                utau, vtau, qns , qsr, emp , emps
113      !!---------------------------------------------------------------------
114      INTEGER, INTENT(in) ::   kt      ! ocean time step
115      INTEGER, INTENT(in) ::   nsbc    ! surface forcing type
116      !!----------------------------------------------------------------------
117      !
118      IF( nn_timing == 1 )  CALL timing_start('sbc_ice_cice')
119      !
120      !                                        !----------------------!
121      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN     !  Ice time-step only  !
122         !                                     !----------------------!
123
124         ! Make sure any fluxes required for CICE are set
125         IF ( nsbc == 2 )  THEN
126            CALL cice_sbc_force(kt)
127         ELSE IF ( nsbc == 5 ) THEN
128            CALL sbc_cpl_ice_flx( 1.0-fr_i  )
129         ENDIF
130
131         CALL cice_sbc_in ( kt, nsbc )
132         CALL CICE_Run
133         CALL cice_sbc_out ( kt, nsbc )
134
135         IF ( nsbc == 5 )  CALL cice_sbc_hadgam(kt+1)
136
137      ENDIF                                          ! End sea-ice time step only
138      !
139      IF( nn_timing == 1 )  CALL timing_stop('sbc_ice_cice')
140
141   END SUBROUTINE sbc_ice_cice
142
143   SUBROUTINE cice_sbc_init (nsbc)
144      !!---------------------------------------------------------------------
145      !!                    ***  ROUTINE cice_sbc_init  ***
146      !! ** Purpose: Initialise ice related fields for NEMO and coupling
147      !!
148      INTEGER, INTENT( in  ) ::   nsbc ! surface forcing type
149      !!---------------------------------------------------------------------
150
151      INTEGER  ::   ji, jj, jl                        ! dummy loop indices
152
153      IF( nn_timing == 1 )  CALL timing_start('cice_sbc_init')
154      !
155      IF(lwp) WRITE(numout,*)'cice_sbc_init'
156
157! Initialize CICE
158      CALL CICE_Initialize
159
160! Do some CICE consistency checks
161      IF ( (nsbc == 2) .OR. (nsbc == 5) ) THEN
162         IF ( calc_strair .OR. calc_Tsfc ) THEN
163            CALL ctl_stop( 'STOP', 'cice_sbc_init : Forcing option requires calc_strair=F and calc_Tsfc=F in ice_in' )
164         ENDIF
165      ELSEIF (nsbc == 4) THEN
166         IF ( .NOT. (calc_strair .AND. calc_Tsfc) ) THEN
167            CALL ctl_stop( 'STOP', 'cice_sbc_init : Forcing option requires calc_strair=T and calc_Tsfc=T in ice_in' )
168         ENDIF
169      ENDIF
170
171
172! allocate sbc_ice and sbc_cice arrays
173      IF( sbc_ice_alloc()      /= 0 )   CALL ctl_stop( 'STOP', 'sbc_ice_cice_alloc : unable to allocate arrays' )
174      IF( sbc_ice_cice_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_ice_cice_alloc : unable to allocate cice arrays' )
175
176! Ensure ocean temperatures are nowhere below freezing if not a NEMO restart
177      IF( .NOT. ln_rstart ) THEN
178         tsn(:,:,:,jp_tem) = MAX (tsn(:,:,:,jp_tem),Tocnfrz)
179         tsb(:,:,:,jp_tem) = tsn(:,:,:,jp_tem)
180      ENDIF
181
182      fr_iu(:,:)=0.0
183      fr_iv(:,:)=0.0
184
185      CALL cice2nemo(aice,fr_i, 'T', 1. )
186      IF ( (nsbc == 2).OR.(nsbc == 5) ) THEN
187         DO jl=1,ncat
188            CALL cice2nemo(aicen(:,:,jl,:),a_i(:,:,jl), 'T', 1. )
189         ENDDO
190      ENDIF
191
192! T point to U point
193! T point to V point
194      DO jj=1,jpjm1
195         DO ji=1,jpim1
196            fr_iu(ji,jj)=0.5*(fr_i(ji,jj)+fr_i(ji+1,jj))*umask(ji,jj,1)
197            fr_iv(ji,jj)=0.5*(fr_i(ji,jj)+fr_i(ji,jj+1))*vmask(ji,jj,1)
198         ENDDO
199      ENDDO
200
201      CALL lbc_lnk ( fr_iu , 'U', 1. )
202      CALL lbc_lnk ( fr_iv , 'V', 1. )
203      !
204      IF( nn_timing == 1 )  CALL timing_stop('cice_sbc_init')
205      !
206   END SUBROUTINE cice_sbc_init
207
208   
209   SUBROUTINE cice_sbc_in (kt, nsbc)
210      !!---------------------------------------------------------------------
211      !!                    ***  ROUTINE cice_sbc_in  ***
212      !! ** Purpose: Set coupling fields and pass to CICE
213      !!---------------------------------------------------------------------
214      INTEGER, INTENT(in   ) ::   kt   ! ocean time step
215      INTEGER, INTENT(in   ) ::   nsbc ! surface forcing type
216
217      INTEGER  ::   ji, jj, jl                   ! dummy loop indices     
218      REAL(wp), DIMENSION(:,:), POINTER :: ztmp
219      REAL(wp), DIMENSION(:,:,:), POINTER :: ztmpn
220      !!---------------------------------------------------------------------
221
222      IF( nn_timing == 1 )  CALL timing_start('cice_sbc_in')
223      !
224      CALL wrk_alloc( jpi,jpj, ztmp )
225      CALL wrk_alloc( jpi,jpj,ncat, ztmpn )
226
227      IF( kt == nit000 )  THEN
228         IF(lwp) WRITE(numout,*)'cice_sbc_in'
229      ENDIF
230
231      ztmp(:,:)=0.0
232
233! Aggregate ice concentration already set in cice_sbc_out (or cice_sbc_init on
234! the first time-step)
235
236! forced and coupled case
237
238      IF ( (nsbc == 2).OR.(nsbc == 5) ) THEN
239
240         ztmpn(:,:,:)=0.0
241
242! x comp of wind stress (CI_1)
243! U point to F point
244         DO jj=1,jpjm1
245            DO ji=1,jpi
246               ztmp(ji,jj) = 0.5 * (  fr_iu(ji,jj) * utau(ji,jj)      &
247                                    + fr_iu(ji,jj+1) * utau(ji,jj+1) ) * fmask(ji,jj,1)
248            ENDDO
249         ENDDO
250         CALL nemo2cice(ztmp,strax,'F', -1. )
251
252! y comp of wind stress (CI_2)
253! V point to F point
254         DO jj=1,jpj
255            DO ji=1,jpim1
256               ztmp(ji,jj) = 0.5 * (  fr_iv(ji,jj) * vtau(ji,jj)      &
257                                    + fr_iv(ji+1,jj) * vtau(ji+1,jj) ) * fmask(ji,jj,1)
258            ENDDO
259         ENDDO
260         CALL nemo2cice(ztmp,stray,'F', -1. )
261
262! Surface downward latent heat flux (CI_5)
263         IF (nsbc == 2) THEN
264            DO jl=1,ncat
265               ztmpn(:,:,jl)=qla_ice(:,:,1)*a_i(:,:,jl)
266            ENDDO
267         ELSE
268! emp_ice is set in sbc_cpl_ice_flx as sublimation-snow
269            qla_ice(:,:,1)= - ( emp_ice(:,:)+sprecip(:,:) ) * Lsub
270! End of temporary code
271            DO jj=1,jpj
272               DO ji=1,jpi
273                  IF (fr_i(ji,jj).eq.0.0) THEN
274                     DO jl=1,ncat
275                        ztmpn(ji,jj,jl)=0.0
276                     ENDDO
277                     ! This will then be conserved in CICE
278                     ztmpn(ji,jj,1)=qla_ice(ji,jj,1)
279                  ELSE
280                     DO jl=1,ncat
281                        ztmpn(ji,jj,jl)=qla_ice(ji,jj,1)*a_i(ji,jj,jl)/fr_i(ji,jj)
282                     ENDDO
283                  ENDIF
284               ENDDO
285            ENDDO
286         ENDIF
287         DO jl=1,ncat
288            CALL nemo2cice(ztmpn(:,:,jl),flatn_f(:,:,jl,:),'T', 1. )
289
290! GBM conductive flux through ice (CI_6)
291!  Convert to GBM
292            IF (nsbc == 2) THEN
293               ztmp(:,:) = botmelt(:,:,jl)*a_i(:,:,jl)
294            ELSE
295               ztmp(:,:) = botmelt(:,:,jl)
296            ENDIF
297            CALL nemo2cice(ztmp,fcondtopn_f(:,:,jl,:),'T', 1. )
298
299! GBM surface heat flux (CI_7)
300!  Convert to GBM
301            IF (nsbc == 2) THEN
302               ztmp(:,:) = (topmelt(:,:,jl)+botmelt(:,:,jl))*a_i(:,:,jl) 
303            ELSE
304               ztmp(:,:) = (topmelt(:,:,jl)+botmelt(:,:,jl))
305            ENDIF
306            CALL nemo2cice(ztmp,fsurfn_f(:,:,jl,:),'T', 1. )
307         ENDDO
308
309      ELSE IF (nsbc == 4) THEN
310
311! Pass CORE forcing fields to CICE (which will calculate heat fluxes etc itself)
312! x comp and y comp of atmosphere surface wind (CICE expects on T points)
313         ztmp(:,:) = wndi_ice(:,:)
314         CALL nemo2cice(ztmp,uatm,'T', -1. )
315         ztmp(:,:) = wndj_ice(:,:)
316         CALL nemo2cice(ztmp,vatm,'T', -1. )
317         ztmp(:,:) = SQRT ( wndi_ice(:,:)**2 + wndj_ice(:,:)**2 )
318         CALL nemo2cice(ztmp,wind,'T', 1. )    ! Wind speed (m/s)
319         ztmp(:,:) = qsr_ice(:,:,1)
320         CALL nemo2cice(ztmp,fsw,'T', 1. )     ! Incoming short-wave (W/m^2)
321         ztmp(:,:) = qlw_ice(:,:,1)
322         CALL nemo2cice(ztmp,flw,'T', 1. )     ! Incoming long-wave (W/m^2)
323         ztmp(:,:) = tatm_ice(:,:)
324         CALL nemo2cice(ztmp,Tair,'T', 1. )    ! Air temperature (K)
325         CALL nemo2cice(ztmp,potT,'T', 1. )    ! Potential temp (K)
326! Following line uses MAX(....) to avoid problems if tatm_ice has unset halo rows 
327         ztmp(:,:) = 101000. / ( 287.04 * MAX(1.0,tatm_ice(:,:)) )   
328                                               ! Constant (101000.) atm pressure assumed
329         CALL nemo2cice(ztmp,rhoa,'T', 1. )    ! Air density (kg/m^3)
330         ztmp(:,:) = qatm_ice(:,:)
331         CALL nemo2cice(ztmp,Qa,'T', 1. )      ! Specific humidity (kg/kg)
332         ztmp(:,:)=10.0
333         CALL nemo2cice(ztmp,zlvl,'T', 1. )    ! Atmos level height (m)
334
335! May want to check all values are physically realistic (as in CICE routine
336! prepare_forcing)?
337
338! Divide shortwave into spectral bands (as in prepare_forcing)
339         ztmp(:,:)=qsr_ice(:,:,1)*frcvdr       ! visible direct
340         CALL nemo2cice(ztmp,swvdr,'T', 1. )             
341         ztmp(:,:)=qsr_ice(:,:,1)*frcvdf       ! visible diffuse
342         CALL nemo2cice(ztmp,swvdf,'T', 1. )             
343         ztmp(:,:)=qsr_ice(:,:,1)*frcidr       ! near IR direct
344         CALL nemo2cice(ztmp,swidr,'T', 1. )
345         ztmp(:,:)=qsr_ice(:,:,1)*frcidf       ! near IR diffuse
346         CALL nemo2cice(ztmp,swidf,'T', 1. )
347
348      ENDIF
349
350! Snowfall
351! Ensure fsnow is positive (as in CICE routine prepare_forcing) 
352      ztmp(:,:)=MAX(fr_i(:,:)*sprecip(:,:),0.0) 
353      CALL nemo2cice(ztmp,fsnow,'T', 1. ) 
354
355! Rainfall
356      ztmp(:,:)=fr_i(:,:)*(tprecip(:,:)-sprecip(:,:))
357      CALL nemo2cice(ztmp,frain,'T', 1. ) 
358
359! Freezing/melting potential
360! Calculated over NEMO leapfrog timestep (hence 2*dt)
361      nfrzmlt(:,:)=rau0*rcp*fse3t_m(:,:,1)*(Tocnfrz-sst_m(:,:))/(2.0*dt)
362
363      ztmp(:,:) = nfrzmlt(:,:)
364      CALL nemo2cice(ztmp,frzmlt,'T', 1. )
365
366! SST  and SSS
367
368      CALL nemo2cice(sst_m,sst,'T', 1. )
369      CALL nemo2cice(sss_m,sss,'T', 1. )
370
371! x comp and y comp of surface ocean current
372! U point to F point
373      DO jj=1,jpjm1
374         DO ji=1,jpi
375            ztmp(ji,jj)=0.5*(ssu_m(ji,jj)+ssu_m(ji,jj+1))*fmask(ji,jj,1)
376         ENDDO
377      ENDDO
378      CALL nemo2cice(ztmp,uocn,'F', -1. )
379
380! V point to F point
381      DO jj=1,jpj
382         DO ji=1,jpim1
383            ztmp(ji,jj)=0.5*(ssv_m(ji,jj)+ssv_m(ji+1,jj))*fmask(ji,jj,1)
384         ENDDO
385      ENDDO
386      CALL nemo2cice(ztmp,vocn,'F', -1. )
387
388! x comp and y comp of sea surface slope (on F points)
389! T point to F point
390      DO jj=1,jpjm1
391         DO ji=1,jpim1
392            ztmp(ji,jj)=0.5 * (  (ssh_m(ji+1,jj  )-ssh_m(ji,jj  ))/e1u(ji,jj  )   &
393                               + (ssh_m(ji+1,jj+1)-ssh_m(ji,jj+1))/e1u(ji,jj+1) ) & 
394                            *  fmask(ji,jj,1)
395         ENDDO
396      ENDDO
397      CALL nemo2cice(ztmp,ss_tltx,'F', -1. )
398
399! T point to F point
400      DO jj=1,jpjm1
401         DO ji=1,jpim1
402            ztmp(ji,jj)=0.5 * (  (ssh_m(ji  ,jj+1)-ssh_m(ji  ,jj))/e2v(ji  ,jj)   &
403                               + (ssh_m(ji+1,jj+1)-ssh_m(ji+1,jj))/e2v(ji+1,jj) ) &
404                            *  fmask(ji,jj,1)
405         ENDDO
406      ENDDO
407      CALL nemo2cice(ztmp,ss_tlty,'F', -1. )
408
409      CALL wrk_dealloc( jpi,jpj, ztmp )
410      CALL wrk_dealloc( jpi,jpj,ncat, ztmpn )
411      !
412      IF( nn_timing == 1 )  CALL timing_stop('cice_sbc_in')
413      !
414   END SUBROUTINE cice_sbc_in
415
416
417   SUBROUTINE cice_sbc_out (kt,nsbc)
418      !!---------------------------------------------------------------------
419      !!                    ***  ROUTINE cice_sbc_out  ***
420      !! ** Purpose: Get fields from CICE and set surface fields for NEMO
421      !!---------------------------------------------------------------------
422      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
423      INTEGER, INTENT( in  ) ::   nsbc ! surface forcing type
424     
425      INTEGER  ::   ji, jj, jl                 ! dummy loop indices
426      REAL(wp), DIMENSION(:,:), POINTER :: ztmp1, ztmp2
427      !!---------------------------------------------------------------------
428
429      IF( nn_timing == 1 )  CALL timing_start('cice_sbc_out')
430      !
431      CALL wrk_alloc( jpi,jpj, ztmp1, ztmp2 )
432     
433      IF( kt == nit000 )  THEN
434         IF(lwp) WRITE(numout,*)'cice_sbc_out'
435      ENDIF
436     
437! x comp of ocean-ice stress
438      CALL cice2nemo(strocnx,ztmp1,'F', -1. )
439      ss_iou(:,:)=0.0
440! F point to U point
441      DO jj=2,jpjm1
442         DO ji=2,jpim1
443            ss_iou(ji,jj) = 0.5 * ( ztmp1(ji,jj-1) + ztmp1(ji,jj) ) * umask(ji,jj,1)
444         ENDDO
445      ENDDO
446      CALL lbc_lnk( ss_iou , 'U', -1. )
447
448! y comp of ocean-ice stress
449      CALL cice2nemo(strocny,ztmp1,'F', -1. )
450      ss_iov(:,:)=0.0
451! F point to V point
452
453      DO jj=1,jpjm1
454         DO ji=2,jpim1
455            ss_iov(ji,jj) = 0.5 * ( ztmp1(ji-1,jj) + ztmp1(ji,jj) ) * vmask(ji,jj,1)
456         ENDDO
457      ENDDO
458      CALL lbc_lnk( ss_iov , 'V', -1. )
459
460! x and y comps of surface stress
461! Combine wind stress and ocean-ice stress
462! [Note that fr_iu hasn't yet been updated, so still from start of CICE timestep]
463
464      utau(:,:)=(1.0-fr_iu(:,:))*utau(:,:)-ss_iou(:,:)
465      vtau(:,:)=(1.0-fr_iv(:,:))*vtau(:,:)-ss_iov(:,:)     
466
467! Freshwater fluxes
468
469      IF (nsbc == 2) THEN
470! Note that emp from the forcing files is evap*(1-aice)-(tprecip-aice*sprecip)
471! What we want here is evap*(1-aice)-tprecip*(1-aice) hence manipulation below
472! Not ideal since aice won't be the same as in the atmosphere. 
473! Better to use evap and tprecip? (but for now don't read in evap in this case)
474         emp(:,:)  = emp(:,:)+fr_i(:,:)*(tprecip(:,:)-sprecip(:,:))
475      ELSE IF (nsbc == 4) THEN
476         emp(:,:)  = (1.0-fr_i(:,:))*emp(:,:)       
477      ELSE IF (nsbc ==5) THEN
478! emp_tot is set in sbc_cpl_ice_flx (call from cice_sbc_in above)
479         emp(:,:) = emp_tot(:,:)+tprecip(:,:)*fr_i(:,:) 
480      ENDIF
481
482      CALL cice2nemo(fresh_gbm,ztmp1,'T', 1. )
483      CALL cice2nemo(fsalt_gbm,ztmp2,'T', 1. )
484! Check to avoid unphysical expression when ice is forming (ztmp1 negative)
485! Otherwise we are effectively allowing ice of higher salinity than the ocean to form
486! which has to be compensated for by the ocean salinity potentially going negative
487! This check breaks conservation but seems reasonable until we have prognostic ice salinity
488! The lines below ensure that when ice is forming emps will not be negative
489! Note the 1000.0 below is to convert from kg salt to g salt (needed for PSU)
490      emps(:,:)=0.0
491      WHERE (ztmp1(:,:).lt.0.0) ztmp2(:,:)=MAX(ztmp2(:,:),ztmp1(:,:)*sss_m(:,:)/1000.0)
492      WHERE (sss_m(:,:).gt.0.0) emps(:,:)=-ztmp1(:,:)+ztmp2(:,:)*1000.0/sss_m(:,:)
493! Now add other non-ice freshwater contributions into emps
494      emps(:,:)=emp(:,:)+emps(:,:)
495 
496      IF (lk_vvl) THEN
497
498! The relevant quantity for calculating the salinity change is emps-emp
499! This is in fact just the ztmp2*1000.0/sss_m term above
500         emp(:,:)=emp(:,:)-ztmp1(:,:)
501
502      ELSE
503
504! Don't remove precip over ice from free surface calculation on basis that the
505! weight of the precip will affect the free surface even if it falls on the ice
506! (same argument that freezing / melting of ice doesn't change the free surface)
507         emp(:,:)  = emp(:,:) - tprecip(:,:)*fr_i(:,:)
508! Sublimation from the ice is treated in a similar way (included in emp but not emps)
509         IF (nsbc == 5 ) THEN
510            emp(:,:) = emp(:,:) + ( emp_ice(:,:) + sprecip(:,:) )
511         ELSE IF (nsbc == 2 ) THEN
512            emp(:,:) = emp(:,:) - qla_ice(:,:,1) / Lsub
513         ENDIF
514
515      ENDIF
516
517      CALL lbc_lnk( emp , 'T', 1. )
518      CALL lbc_lnk( emps , 'T', 1. )
519
520! Solar penetrative radiation and non solar surface heat flux
521
522! Scale qsr and qns according to ice fraction (bulk formulae only)
523
524      IF (nsbc == 4) THEN
525         qsr(:,:)=qsr(:,:)*(1.0-fr_i(:,:))
526         qns(:,:)=qns(:,:)*(1.0-fr_i(:,:))
527      ENDIF
528! Take into account snow melting except for fully coupled when already in qns_tot
529      IF (nsbc == 5) THEN
530         qsr(:,:)= qsr_tot(:,:)
531         qns(:,:)= qns_tot(:,:)
532      ELSE
533         qns(:,:)= qns(:,:)-sprecip(:,:)*Lfresh*(1.0-fr_i(:,:))
534      ENDIF
535
536! Now add in ice / snow related terms
537! [fswthru will be zero unless running with calc_Tsfc=T in CICE]
538      CALL cice2nemo(fswthru_gbm,ztmp1,'T', 1. )
539      qsr(:,:)=qsr(:,:)+ztmp1(:,:)
540      CALL lbc_lnk( qsr , 'T', 1. )
541
542      DO jj=1,jpj
543         DO ji=1,jpi
544            nfrzmlt(ji,jj)=MAX(nfrzmlt(ji,jj),0.0)
545         ENDDO
546      ENDDO
547
548      CALL cice2nemo(fhocn_gbm,ztmp1,'T', 1. )
549      qns(:,:)=qns(:,:)+nfrzmlt(:,:)+ztmp1(:,:)
550
551      CALL lbc_lnk( qns , 'T', 1. )
552
553! Prepare for the following CICE time-step
554
555      CALL cice2nemo(aice,fr_i,'T', 1. )
556      IF ( (nsbc == 2).OR.(nsbc == 5) ) THEN
557         DO jl=1,ncat
558            CALL cice2nemo(aicen(:,:,jl,:),a_i(:,:,jl), 'T', 1. )
559         ENDDO
560      ENDIF
561
562! T point to U point
563! T point to V point
564      DO jj=1,jpjm1
565         DO ji=1,jpim1
566            fr_iu(ji,jj)=0.5*(fr_i(ji,jj)+fr_i(ji+1,jj))*umask(ji,jj,1)
567            fr_iv(ji,jj)=0.5*(fr_i(ji,jj)+fr_i(ji,jj+1))*vmask(ji,jj,1)
568         ENDDO
569      ENDDO
570
571      CALL lbc_lnk ( fr_iu , 'U', 1. )
572      CALL lbc_lnk ( fr_iv , 'V', 1. )
573
574! Release work space
575
576      CALL wrk_dealloc( jpi,jpj, ztmp1, ztmp2 )
577      !
578      IF( nn_timing == 1 )  CALL timing_stop('cice_sbc_out')
579      !
580   END SUBROUTINE cice_sbc_out
581
582
583#if defined key_oasis3 || defined key_oasis4
584   SUBROUTINE cice_sbc_hadgam( kt )
585      !!---------------------------------------------------------------------
586      !!                    ***  ROUTINE cice_sbc_hadgam  ***
587      !! ** Purpose: Prepare fields needed to pass to HadGAM3 atmosphere
588      !!
589      !!
590      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
591      !!---------------------------------------------------------------------
592
593      INTEGER  ::   jl                        ! dummy loop index
594      INTEGER  ::   ierror
595
596      IF( nn_timing == 1 )  CALL timing_start('cice_sbc_hadgam')
597      !
598      IF( kt == nit000 )  THEN
599         IF(lwp) WRITE(numout,*)'cice_sbc_hadgam'
600         IF( sbc_cpl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' )
601      ENDIF
602
603      !                                         ! =========================== !
604      !                                         !   Prepare Coupling fields   !
605      !                                         ! =========================== !
606
607! x and y comp of ice velocity
608
609      CALL cice2nemo(uvel,u_ice,'F', -1. )
610      CALL cice2nemo(vvel,v_ice,'F', -1. )
611
612! Ice concentration (CO_1) = a_i calculated at end of cice_sbc_out 
613
614! Snow and ice thicknesses (CO_2 and CO_3)
615
616      DO jl = 1,ncat
617         CALL cice2nemo(vsnon(:,:,jl,:),ht_s(:,:,jl),'T', 1. )
618         CALL cice2nemo(vicen(:,:,jl,:),ht_i(:,:,jl),'T', 1. )
619      ENDDO
620      !
621      IF( nn_timing == 1 )  CALL timing_stop('cice_sbc_hadgam')
622      !
623   END SUBROUTINE cice_sbc_hadgam
624
625#else
626   SUBROUTINE cice_sbc_hadgam( kt )    ! Dummy routine
627      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
628      WRITE(*,*) 'cice_sbc_hadgam: You should not have seen this print! error?'
629   END SUBROUTINE cice_sbc_hadgam
630#endif
631
632   SUBROUTINE cice_sbc_final
633      !!---------------------------------------------------------------------
634      !!                    ***  ROUTINE cice_sbc_final  ***
635      !! ** Purpose: Finalize CICE
636      !!---------------------------------------------------------------------
637
638      IF(lwp) WRITE(numout,*)'cice_sbc_final'
639
640      CALL CICE_Finalize
641
642   END SUBROUTINE cice_sbc_final
643
644   SUBROUTINE cice_sbc_force (kt)
645      !!---------------------------------------------------------------------
646      !!                    ***  ROUTINE cice_sbc_force  ***
647      !! ** Purpose : Provide CICE forcing from files
648      !!
649      !!---------------------------------------------------------------------
650      !! ** Method  :   READ monthly flux file in NetCDF files
651      !!     
652      !!  snowfall   
653      !!  rainfall   
654      !!  sublimation rate   
655      !!  topmelt (category)
656      !!  botmelt (category)
657      !!
658      !! History :
659      !!----------------------------------------------------------------------
660      !! * Modules used
661      USE iom
662
663      !! * arguments
664      INTEGER, INTENT( in  ) ::   kt ! ocean time step
665
666      INTEGER  ::   ierror             ! return error code
667      INTEGER  ::   ifpr               ! dummy loop index
668      !!
669      CHARACTER(len=100) ::  cn_dir                            !   Root directory for location of CICE forcing files
670      TYPE(FLD_N), DIMENSION(jpfld) ::   slf_i                 ! array of namelist informations on the fields to read
671      TYPE(FLD_N) ::   sn_snow, sn_rain, sn_sblm               ! informations about the fields to be read
672      TYPE(FLD_N) ::   sn_top1, sn_top2, sn_top3, sn_top4, sn_top5
673      TYPE(FLD_N) ::   sn_bot1, sn_bot2, sn_bot3, sn_bot4, sn_bot5 
674
675      !!
676      NAMELIST/namsbc_cice/ cn_dir, sn_snow, sn_rain, sn_sblm,   &
677         &                          sn_top1, sn_top2, sn_top3, sn_top4, sn_top5,  &
678         &                          sn_bot1, sn_bot2, sn_bot3, sn_bot4, sn_bot5
679      !!---------------------------------------------------------------------
680
681      !                                         ! ====================== !
682      IF( kt == nit000 ) THEN                   !  First call kt=nit000  !
683         !                                      ! ====================== !
684         ! set file information (default values)
685         cn_dir = './'       ! directory in which the model is executed
686
687         ! (NB: frequency positive => hours, negative => months)
688         !            !    file          ! frequency !  variable    ! time intep !  clim   ! 'yearly' or ! weights  ! rotation   !
689         !            !    name          !  (hours)  !   name       !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs      !
690         sn_snow = FLD_N( 'snowfall_1m'  ,    -1.    ,  'snowfall'  ,  .true.    , .true.  ,  ' yearly'  , ''       , ''         ) 
691         sn_rain = FLD_N( 'rainfall_1m'  ,    -1.    ,  'rainfall'  ,  .true.    , .true.  ,  ' yearly'  , ''       , ''         ) 
692         sn_sblm = FLD_N( 'sublim_1m'    ,    -1.    ,  'sublim'    ,  .true.    , .true.  ,  ' yearly'  , ''       , ''         )
693         sn_top1 = FLD_N( 'topmeltn1_1m' ,    -1.    ,  'topmeltn1' ,  .true.    , .true.  ,  ' yearly'  , ''       , ''         )
694         sn_top2 = FLD_N( 'topmeltn2_1m' ,    -1.    ,  'topmeltn2' ,  .true.    , .true.  ,  ' yearly'  , ''       , ''         )
695         sn_top3 = FLD_N( 'topmeltn3_1m' ,    -1.    ,  'topmeltn3' ,  .true.    , .true.  ,  ' yearly'  , ''       , ''         )
696         sn_top4 = FLD_N( 'topmeltn4_1m' ,    -1.    ,  'topmeltn4' ,  .true.    , .true.  ,  ' yearly'  , ''       , ''         )
697         sn_top5 = FLD_N( 'topmeltn5_1m' ,    -1.    ,  'topmeltn5' ,  .true.    , .true.  ,  ' yearly'  , ''       , ''         )
698         sn_bot1 = FLD_N( 'botmeltn1_1m' ,    -1.    ,  'botmeltn1' ,  .true.    , .true.  ,  ' yearly'  , ''       , ''         )
699         sn_bot2 = FLD_N( 'botmeltn2_1m' ,    -1.    ,  'botmeltn2' ,  .true.    , .true.  ,  ' yearly'  , ''       , ''         )
700         sn_bot3 = FLD_N( 'botmeltn3_1m' ,    -1.    ,  'botmeltn3' ,  .true.    , .true.  ,  ' yearly'  , ''       , ''         )
701         sn_bot4 = FLD_N( 'botmeltn4_1m' ,    -1.    ,  'botmeltn4' ,  .true.    , .true.  ,  ' yearly'  , ''       , ''         )
702         sn_bot5 = FLD_N( 'botmeltn5_1m' ,    -1.    ,  'botmeltn5' ,  .true.    , .true.  ,  ' yearly'  , ''       , ''         )
703
704!         REWIND ( numnam )               ! ... at some point might read in from NEMO namelist?
705!         READ   ( numnam, namsbc_cice )
706
707         ! store namelist information in an array
708         slf_i(jp_snow) = sn_snow   ;   slf_i(jp_rain) = sn_rain   ;   slf_i(jp_sblm) = sn_sblm
709         slf_i(jp_top1) = sn_top1   ;   slf_i(jp_top2) = sn_top2   ;   slf_i(jp_top3) = sn_top3
710         slf_i(jp_top4) = sn_top4   ;   slf_i(jp_top5) = sn_top5   ;   slf_i(jp_bot1) = sn_bot1
711         slf_i(jp_bot2) = sn_bot2   ;   slf_i(jp_bot3) = sn_bot3   ;   slf_i(jp_bot4) = sn_bot4
712         slf_i(jp_bot5) = sn_bot5
713         
714         ! set sf structure
715         ALLOCATE( sf(jpfld), STAT=ierror )
716         IF( ierror > 0 ) THEN
717            CALL ctl_stop( 'cice_sbc_force: unable to allocate sf structure' )   ;   RETURN
718         ENDIF
719
720         DO ifpr= 1, jpfld
721            ALLOCATE( sf(ifpr)%fnow(jpi,jpj,1) )
722            ALLOCATE( sf(ifpr)%fdta(jpi,jpj,1,2) )
723         END DO
724
725         ! fill sf with slf_i and control print
726         CALL fld_fill( sf, slf_i, cn_dir, 'cice_sbc_force', 'flux formulation for CICE', 'namsbc_cice' )
727         !
728      ENDIF
729
730      CALL fld_read( kt, nn_fsbc, sf )           ! Read input fields and provides the
731      !                                          ! input fields at the current time-step
732
733      ! set the fluxes from read fields
734      sprecip(:,:) = sf(jp_snow)%fnow(:,:,1)
735      tprecip(:,:) = sf(jp_snow)%fnow(:,:,1)+sf(jp_rain)%fnow(:,:,1)
736! May be better to do this conversion somewhere else
737      qla_ice(:,:,1) = -Lsub*sf(jp_sblm)%fnow(:,:,1)
738      topmelt(:,:,1) = sf(jp_top1)%fnow(:,:,1)
739      topmelt(:,:,2) = sf(jp_top2)%fnow(:,:,1)
740      topmelt(:,:,3) = sf(jp_top3)%fnow(:,:,1)
741      topmelt(:,:,4) = sf(jp_top4)%fnow(:,:,1)
742      topmelt(:,:,5) = sf(jp_top5)%fnow(:,:,1)
743      botmelt(:,:,1) = sf(jp_bot1)%fnow(:,:,1)
744      botmelt(:,:,2) = sf(jp_bot2)%fnow(:,:,1)
745      botmelt(:,:,3) = sf(jp_bot3)%fnow(:,:,1)
746      botmelt(:,:,4) = sf(jp_bot4)%fnow(:,:,1)
747      botmelt(:,:,5) = sf(jp_bot5)%fnow(:,:,1)
748
749      ! control print (if less than 100 time-step asked)
750      IF( nitend-nit000 <= 100 .AND. lwp ) THEN
751         WRITE(numout,*) 
752         WRITE(numout,*) '        read forcing fluxes for CICE OK'
753         CALL FLUSH(numout)
754      ENDIF
755
756   END SUBROUTINE cice_sbc_force
757
758   SUBROUTINE nemo2cice( pn, pc, cd_type, psgn)
759      !!---------------------------------------------------------------------
760      !!                    ***  ROUTINE nemo2cice  ***
761      !! ** Purpose :   Transfer field in NEMO array to field in CICE array. 
762#if defined key_nemocice_decomp
763      !!             
764      !!                NEMO and CICE PE sub domains are identical, hence
765      !!                there is no need to gather or scatter data from
766      !!                one PE configuration to another.
767#else
768      !!                Automatically gather/scatter between
769      !!                different processors and blocks
770      !! ** Method :    A. Ensure all haloes are filled in NEMO field (pn)
771      !!                B. Gather pn into global array (png)
772      !!                C. Map png into CICE global array (pcg)
773      !!                D. Scatter pcg to CICE blocks (pc) + update haloes 
774#endif
775      !!---------------------------------------------------------------------
776
777      CHARACTER(len=1), INTENT( in ) ::   &
778          cd_type       ! nature of pn grid-point
779          !             !   = T or F gridpoints
780      REAL(wp), INTENT( in ) ::   &
781          psgn          ! control of the sign change
782          !             !   =-1 , the sign is modified following the type of b.c. used
783          !             !   = 1 , no sign change
784      REAL(wp), DIMENSION(jpi,jpj) :: pn
785#if !defined key_nemocice_decomp
786      REAL(wp), DIMENSION(jpiglo,jpjglo) :: png2
787      REAL (kind=dbl_kind), dimension(nx_global,ny_global) :: pcg
788#endif
789      REAL (kind=dbl_kind), dimension(nx_block,ny_block,max_blocks) :: pc
790      INTEGER (int_kind) :: &
791         field_type,        &! id for type of field (scalar, vector, angle)
792         grid_loc            ! id for location on horizontal grid
793                            !  (center, NEcorner, Nface, Eface)
794
795      INTEGER  ::   ji, jj, jn                      ! dummy loop indices
796
797!     A. Ensure all haloes are filled in NEMO field (pn)
798
799      CALL lbc_lnk( pn , cd_type, psgn )
800
801#if defined key_nemocice_decomp
802
803      ! Copy local domain data from NEMO to CICE field
804      pc(:,:,1)=0.0
805      DO jj=2,ny_block-1
806         DO ji=2,nx_block-1
807            pc(ji,jj,1)=pn(ji-1+ji_off,jj-1+jj_off)
808         ENDDO
809      ENDDO
810
811#else
812
813!     B. Gather pn into global array (png)
814
815      IF ( jpnij > 1) THEN
816         CALL mppsync
817         CALL mppgather (pn,0,png) 
818         CALL mppsync
819      ELSE
820         png(:,:,1)=pn(:,:)
821      ENDIF
822
823!     C. Map png into CICE global array (pcg)
824
825! Need to make sure this is robust to changes in NEMO halo rows....
826! (may be OK but not 100% sure)
827
828      IF (nproc==0) THEN     
829!        pcg(:,:)=0.0
830         DO jn=1,jpnij
831            DO jj=nldjt(jn),nlejt(jn)
832               DO ji=nldit(jn),nleit(jn)
833                  png2(ji+nimppt(jn)-1,jj+njmppt(jn)-1)=png(ji,jj,jn)
834               ENDDO
835            ENDDO
836         ENDDO
837         DO jj=1,ny_global
838            DO ji=1,nx_global
839               pcg(ji,jj)=png2(ji+ji_off,jj+jj_off)
840            ENDDO
841         ENDDO
842      ENDIF
843
844#endif
845
846      SELECT CASE ( cd_type )
847         CASE ( 'T' )
848            grid_loc=field_loc_center
849         CASE ( 'F' )                             
850            grid_loc=field_loc_NEcorner
851      END SELECT
852
853      SELECT CASE ( NINT(psgn) )
854         CASE ( -1 )
855            field_type=field_type_vector
856         CASE ( 1 )                             
857            field_type=field_type_scalar
858      END SELECT
859
860#if defined key_nemocice_decomp
861      ! Ensure CICE halos are up to date
862      CALL ice_HaloUpdate (pc, halo_info, grid_loc, field_type)
863#else
864!     D. Scatter pcg to CICE blocks (pc) + update halos
865      CALL scatter_global(pc, pcg, 0, distrb_info, grid_loc, field_type)
866#endif
867
868   END SUBROUTINE nemo2cice
869
870   SUBROUTINE cice2nemo ( pc, pn, cd_type, psgn )
871      !!---------------------------------------------------------------------
872      !!                    ***  ROUTINE cice2nemo  ***
873      !! ** Purpose :   Transfer field in CICE array to field in NEMO array.
874#if defined key_nemocice_decomp
875      !!             
876      !!                NEMO and CICE PE sub domains are identical, hence
877      !!                there is no need to gather or scatter data from
878      !!                one PE configuration to another.
879#else 
880      !!                Automatically deal with scatter/gather between
881      !!                different processors and blocks
882      !! ** Method :    A. Gather CICE blocks (pc) into global array (pcg)
883      !!                B. Map pcg into NEMO global array (png)
884      !!                C. Scatter png into NEMO field (pn) for each processor
885      !!                D. Ensure all haloes are filled in pn
886#endif
887      !!---------------------------------------------------------------------
888
889      CHARACTER(len=1), INTENT( in ) ::   &
890          cd_type       ! nature of pn grid-point
891          !             !   = T or F gridpoints
892      REAL(wp), INTENT( in ) ::   &
893          psgn          ! control of the sign change
894          !             !   =-1 , the sign is modified following the type of b.c. used
895          !             !   = 1 , no sign change
896      REAL(wp), DIMENSION(jpi,jpj) :: pn
897
898#if defined key_nemocice_decomp
899      INTEGER (int_kind) :: &
900         field_type,        & ! id for type of field (scalar, vector, angle)
901         grid_loc             ! id for location on horizontal grid
902                              ! (center, NEcorner, Nface, Eface)
903#else
904      REAL (kind=dbl_kind), dimension(nx_global,ny_global) :: pcg
905#endif
906
907      REAL (kind=dbl_kind), dimension(nx_block,ny_block,max_blocks) :: pc
908
909      INTEGER  ::   ji, jj, jn                      ! dummy loop indices
910
911
912#if defined key_nemocice_decomp
913
914      SELECT CASE ( cd_type )
915         CASE ( 'T' )
916            grid_loc=field_loc_center
917         CASE ( 'F' )                             
918            grid_loc=field_loc_NEcorner
919      END SELECT
920
921      SELECT CASE ( NINT(psgn) )
922         CASE ( -1 )
923            field_type=field_type_vector
924         CASE ( 1 )                             
925            field_type=field_type_scalar
926      END SELECT
927
928      CALL ice_HaloUpdate (pc, halo_info, grid_loc, field_type)
929
930
931      pn(:,:)=0.0
932      DO jj=1,jpjm1
933         DO ji=1,jpim1
934            pn(ji,jj)=pc(ji+1-ji_off,jj+1-jj_off,1)
935         ENDDO
936      ENDDO
937
938#else
939
940!      A. Gather CICE blocks (pc) into global array (pcg)
941
942      CALL gather_global(pcg, pc, 0, distrb_info)
943
944!     B. Map pcg into NEMO global array (png)
945
946! Need to make sure this is robust to changes in NEMO halo rows....
947! (may be OK but not spent much time thinking about it)
948! Note that non-existent pcg elements may be used below, but
949! the lbclnk call on pn will replace these with sensible values
950
951      IF (nproc==0) THEN
952         png(:,:,:)=0.0
953         DO jn=1,jpnij
954            DO jj=nldjt(jn),nlejt(jn)
955               DO ji=nldit(jn),nleit(jn)
956                  png(ji,jj,jn)=pcg(ji+nimppt(jn)-1-ji_off,jj+njmppt(jn)-1-jj_off)
957               ENDDO
958            ENDDO
959         ENDDO
960      ENDIF
961
962!     C. Scatter png into NEMO field (pn) for each processor
963
964      IF ( jpnij > 1) THEN
965         CALL mppsync
966         CALL mppscatter (png,0,pn) 
967         CALL mppsync
968      ELSE
969         pn(:,:)=png(:,:,1)
970      ENDIF
971
972#endif
973
974!     D. Ensure all haloes are filled in pn
975
976      CALL lbc_lnk( pn , cd_type, psgn )
977
978   END SUBROUTINE cice2nemo
979
980#else
981   !!----------------------------------------------------------------------
982   !!   Default option           Dummy module         NO CICE sea-ice model
983   !!----------------------------------------------------------------------
984CONTAINS
985
986   SUBROUTINE sbc_ice_cice ( kt, nsbc )     ! Dummy routine
987      WRITE(*,*) 'sbc_ice_cice: You should not have seen this print! error?', kt
988   END SUBROUTINE sbc_ice_cice
989
990   SUBROUTINE cice_sbc_init (nsbc)    ! Dummy routine
991      WRITE(*,*) 'cice_sbc_init: You should not have seen this print! error?'
992   END SUBROUTINE cice_sbc_init
993
994   SUBROUTINE cice_sbc_final     ! Dummy routine
995      WRITE(*,*) 'cice_sbc_final: You should not have seen this print! error?'
996   END SUBROUTINE cice_sbc_final
997
998#endif
999
1000   !!======================================================================
1001END MODULE sbcice_cice
Note: See TracBrowser for help on using the repository browser.