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

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

#953 Changes to ensure CICE interface will work in regional as well as global configurations.

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