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.
Changeset 3094 for branches/2011/dev_NOC_UKMO_MERGE/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

Ignore:
Timestamp:
2011-11-14T16:28:04+01:00 (13 years ago)
Author:
acc
Message:

Branch dev_NOC_UKMO_MERGE #890. Step 2. Merge in changes from the dev_UKM0_2011 branch with unwanted changes reverted

Location:
branches/2011/dev_NOC_UKMO_MERGE/NEMOGCM/NEMO/OPA_SRC/SBC
Files:
9 edited
1 copied

Legend:

Unmodified
Added
Removed
  • branches/2011/dev_NOC_UKMO_MERGE/NEMOGCM/NEMO/OPA_SRC/SBC/cpl_oasis3.F90

    r2715 r3094  
    1313   !!   " "  !  06-01  (W. Park) modification of physical part 
    1414   !!   " "  !  06-02  (R. Redler, W. Park) buffer array fix for root exchange 
     15   !!   3.4  !  11-11  (C. Harris) Changes to allow mutiple category fields 
    1516   !!---------------------------------------------------------------------- 
    1617#if defined key_oasis3 
     
    5253   INTEGER, PARAMETER ::   nmaxfld=40    ! Maximum number of coupling fields 
    5354    
    54    TYPE, PUBLIC ::   FLD_CPL            !: Type for coupling field information 
    55       LOGICAL            ::   laction   ! To be coupled or not 
    56       CHARACTER(len = 8) ::   clname    ! Name of the coupling field    
    57       CHARACTER(len = 1) ::   clgrid    ! Grid type   
    58       REAL(wp)           ::   nsgn      ! Control of the sign change 
    59       INTEGER            ::   nid       ! Id of the field 
     55   TYPE, PUBLIC ::   FLD_CPL               !: Type for coupling field information 
     56      LOGICAL               ::   laction   ! To be coupled or not 
     57      CHARACTER(len = 8)    ::   clname    ! Name of the coupling field    
     58      CHARACTER(len = 1)    ::   clgrid    ! Grid type   
     59      REAL(wp)              ::   nsgn      ! Control of the sign change 
     60      INTEGER, DIMENSION(9) ::   nid       ! Id of the field (no more than 9 categories) 
     61      INTEGER               ::   nct       ! Number of categories in field 
    6062   END TYPE FLD_CPL 
    6163 
     
    118120      INTEGER :: paral(5)       ! OASIS3 box partition 
    119121      INTEGER :: ishape(2,2)    ! shape of arrays passed to PSMILe 
    120       INTEGER :: ji             ! local loop indicees 
     122      INTEGER :: ji,jc          ! local loop indicees 
     123      CHARACTER(LEN=8) :: zclname 
    121124      !!-------------------------------------------------------------------- 
    122125 
     
    164167      DO ji = 1, ksnd 
    165168         IF ( ssnd(ji)%laction ) THEN  
    166             CALL prism_def_var_proto (ssnd(ji)%nid, ssnd(ji)%clname, id_part, (/ 2, 0/),  & 
    167                &                      PRISM_Out   , ishape   , PRISM_REAL, nerror) 
    168             IF ( nerror /= PRISM_Ok ) THEN 
    169                WRITE(numout,*) 'Failed to define transient ', ji, TRIM(ssnd(ji)%clname) 
    170                CALL prism_abort_proto ( ssnd(ji)%nid, 'cpl_prism_define', 'Failure in prism_def_var') 
    171             ENDIF 
     169            DO jc = 1, ssnd(ji)%nct 
     170               IF ( ssnd(ji)%nct .gt. 1 ) THEN 
     171                  WRITE(zclname,'( a7, i1)') ssnd(ji)%clname,jc 
     172               ELSE 
     173                  zclname=ssnd(ji)%clname 
     174               ENDIF 
     175               WRITE(numout,*) "Define",ji,jc,zclname," for",PRISM_Out 
     176               CALL prism_def_var_proto (ssnd(ji)%nid(jc), zclname, id_part, (/ 2, 0/),   & 
     177                    PRISM_Out, ishape, PRISM_REAL, nerror) 
     178               IF ( nerror /= PRISM_Ok ) THEN 
     179                  WRITE(numout,*) 'Failed to define transient ', ji, TRIM(zclname) 
     180                  CALL prism_abort_proto ( ssnd(ji)%nid(jc), 'cpl_prism_define', 'Failure in prism_def_var') 
     181               ENDIF 
     182            END DO 
    172183         ENDIF 
    173184      END DO 
     
    177188      DO ji = 1, krcv 
    178189         IF ( srcv(ji)%laction ) THEN  
    179             CALL prism_def_var_proto ( srcv(ji)%nid, srcv(ji)%clname, id_part, (/ 2, 0/),   & 
    180                &                      PRISM_In    , ishape   , PRISM_REAL, nerror) 
    181             IF ( nerror /= PRISM_Ok ) THEN 
    182                WRITE(numout,*) 'Failed to define transient ', ji, TRIM(srcv(ji)%clname) 
    183                CALL prism_abort_proto ( srcv(ji)%nid, 'cpl_prism_define', 'Failure in prism_def_var') 
    184             ENDIF 
     190            DO jc = 1, srcv(ji)%nct 
     191               IF ( srcv(ji)%nct .gt. 1 ) THEN 
     192                  WRITE(zclname,'( a7, i1)') srcv(ji)%clname,jc 
     193               ELSE 
     194                  zclname=srcv(ji)%clname 
     195               ENDIF 
     196               WRITE(numout,*) "Define",ji,jc,zclname," for",PRISM_In 
     197               CALL prism_def_var_proto ( srcv(ji)%nid(jc), zclname, id_part, (/ 2, 0/),   & 
     198                    &                      PRISM_In    , ishape   , PRISM_REAL, nerror) 
     199               IF ( nerror /= PRISM_Ok ) THEN 
     200                  WRITE(numout,*) 'Failed to define transient ', ji, TRIM(zclname) 
     201                  CALL prism_abort_proto ( srcv(ji)%nid(jc), 'cpl_prism_define', 'Failure in prism_def_var') 
     202               ENDIF 
     203            END DO 
    185204         ENDIF 
    186205      END DO 
     
    203222      !!      like sst or ice cover to the coupler or remote application. 
    204223      !!---------------------------------------------------------------------- 
    205       INTEGER                 , INTENT(in   ) ::   kid       ! variable index in the array 
    206       INTEGER                 , INTENT(  out) ::   kinfo     ! OASIS3 info argument 
    207       INTEGER                 , INTENT(in   ) ::   kstep     ! ocean time-step in seconds 
    208       REAL(wp), DIMENSION(:,:), INTENT(in   ) ::   pdata 
     224      INTEGER                   , INTENT(in   ) ::   kid       ! variable index in the array 
     225      INTEGER                   , INTENT(  out) ::   kinfo     ! OASIS3 info argument 
     226      INTEGER                   , INTENT(in   ) ::   kstep     ! ocean time-step in seconds 
     227      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   pdata 
     228      !! 
     229      INTEGER                                   ::   jc        ! local loop index 
    209230      !!-------------------------------------------------------------------- 
    210231      ! 
    211232      ! snd data to OASIS3 
    212233      ! 
    213       CALL prism_put_proto ( ssnd(kid)%nid, kstep, pdata(nldi:nlei, nldj:nlej), kinfo ) 
    214        
    215       IF ( ln_ctl ) THEN         
    216          IF ( kinfo == PRISM_Sent     .OR. kinfo == PRISM_ToRest .OR.   & 
    217             & kinfo == PRISM_SentOut  .OR. kinfo == PRISM_ToRestOut ) THEN 
    218             WRITE(numout,*) '****************' 
    219             WRITE(numout,*) 'prism_put_proto: Outgoing ', ssnd(kid)%clname 
    220             WRITE(numout,*) 'prism_put_proto: ivarid ', ssnd(kid)%nid 
    221             WRITE(numout,*) 'prism_put_proto:  kstep ', kstep 
    222             WRITE(numout,*) 'prism_put_proto:   info ', kinfo 
    223             WRITE(numout,*) '     - Minimum value is ', MINVAL(pdata) 
    224             WRITE(numout,*) '     - Maximum value is ', MAXVAL(pdata) 
    225             WRITE(numout,*) '     -     Sum value is ', SUM(pdata) 
    226             WRITE(numout,*) '****************' 
     234      DO jc = 1, ssnd(kid)%nct 
     235 
     236         CALL prism_put_proto ( ssnd(kid)%nid(jc), kstep, pdata(nldi:nlei, nldj:nlej,jc), kinfo ) 
     237          
     238         IF ( ln_ctl ) THEN         
     239            IF ( kinfo == PRISM_Sent     .OR. kinfo == PRISM_ToRest .OR.   & 
     240                 & kinfo == PRISM_SentOut  .OR. kinfo == PRISM_ToRestOut ) THEN 
     241               WRITE(numout,*) '****************' 
     242               WRITE(numout,*) 'prism_put_proto: Outgoing ', ssnd(kid)%clname 
     243               WRITE(numout,*) 'prism_put_proto: ivarid ', ssnd(kid)%nid(jc) 
     244               WRITE(numout,*) 'prism_put_proto:  kstep ', kstep 
     245               WRITE(numout,*) 'prism_put_proto:   info ', kinfo 
     246               WRITE(numout,*) '     - Minimum value is ', MINVAL(pdata(:,:,jc)) 
     247               WRITE(numout,*) '     - Maximum value is ', MAXVAL(pdata(:,:,jc)) 
     248               WRITE(numout,*) '     -     Sum value is ', SUM(pdata(:,:,jc)) 
     249               WRITE(numout,*) '****************' 
     250            ENDIF 
    227251         ENDIF 
    228       ENDIF 
     252 
     253      ENDDO 
    229254      ! 
    230255    END SUBROUTINE cpl_prism_snd 
     
    238263      !!      like stresses and fluxes from the coupler or remote application. 
    239264      !!---------------------------------------------------------------------- 
    240       INTEGER                 , INTENT(in   ) ::   kid       ! variable index in the array 
    241       INTEGER                 , INTENT(in   ) ::   kstep     ! ocean time-step in seconds 
    242       REAL(wp), DIMENSION(:,:), INTENT(inout) ::   pdata     ! IN to keep the value if nothing is done 
    243       INTEGER                 , INTENT(  out) ::   kinfo     ! OASIS3 info argument 
    244       !! 
    245       LOGICAL ::   llaction 
     265      INTEGER                   , INTENT(in   ) ::   kid       ! variable index in the array 
     266      INTEGER                   , INTENT(in   ) ::   kstep     ! ocean time-step in seconds 
     267      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   pdata     ! IN to keep the value if nothing is done 
     268      INTEGER                   , INTENT(  out) ::   kinfo     ! OASIS3 info argument 
     269      !! 
     270      INTEGER                                   ::   jc        ! local loop index 
     271      LOGICAL                                   ::   llaction 
    246272      !!-------------------------------------------------------------------- 
    247273      ! 
    248274      ! receive local data from OASIS3 on every process 
    249275      ! 
    250       CALL prism_get_proto ( srcv(kid)%nid, kstep, exfld, kinfo )          
    251  
    252       llaction = .false. 
    253       IF( kinfo == PRISM_Recvd   .OR. kinfo == PRISM_FromRest .OR.   & 
    254           kinfo == PRISM_RecvOut .OR. kinfo == PRISM_FromRestOut )   llaction = .TRUE. 
    255  
    256       IF ( ln_ctl )   WRITE(numout,*) "llaction, kinfo, kstep, ivarid: " , llaction, kinfo, kstep, srcv(kid)%nid 
    257  
    258       IF ( llaction ) THEN 
    259  
    260          kinfo = OASIS_Rcv 
    261          pdata(nldi:nlei, nldj:nlej) = exfld(:,:) 
    262           
    263          !--- Fill the overlap areas and extra hallows (mpp) 
    264          !--- check periodicity conditions (all cases) 
    265          CALL lbc_lnk( pdata, srcv(kid)%clgrid, srcv(kid)%nsgn )    
    266           
    267          IF ( ln_ctl ) THEN         
    268             WRITE(numout,*) '****************' 
    269             WRITE(numout,*) 'prism_get_proto: Incoming ', srcv(kid)%clname 
    270             WRITE(numout,*) 'prism_get_proto: ivarid '  , srcv(kid)%nid 
    271             WRITE(numout,*) 'prism_get_proto:   kstep', kstep 
    272             WRITE(numout,*) 'prism_get_proto:   info ', kinfo 
    273             WRITE(numout,*) '     - Minimum value is ', MINVAL(pdata) 
    274             WRITE(numout,*) '     - Maximum value is ', MAXVAL(pdata) 
    275             WRITE(numout,*) '     -     Sum value is ', SUM(pdata) 
    276             WRITE(numout,*) '****************' 
     276      DO jc = 1, srcv(kid)%nct 
     277 
     278         CALL prism_get_proto ( srcv(kid)%nid(jc), kstep, exfld, kinfo )          
     279          
     280         llaction = .false. 
     281         IF( kinfo == PRISM_Recvd   .OR. kinfo == PRISM_FromRest .OR.   & 
     282              kinfo == PRISM_RecvOut .OR. kinfo == PRISM_FromRestOut )   llaction = .TRUE. 
     283          
     284         IF ( ln_ctl )   WRITE(numout,*) "llaction, kinfo, kstep, ivarid: " , llaction, kinfo, kstep, srcv(kid)%nid(jc) 
     285          
     286         IF ( llaction ) THEN 
     287             
     288            kinfo = OASIS_Rcv 
     289            pdata(nldi:nlei, nldj:nlej,jc) = exfld(:,:) 
     290             
     291            !--- Fill the overlap areas and extra hallows (mpp) 
     292            !--- check periodicity conditions (all cases) 
     293            CALL lbc_lnk( pdata(:,:,jc), srcv(kid)%clgrid, srcv(kid)%nsgn )    
     294             
     295            IF ( ln_ctl ) THEN         
     296               WRITE(numout,*) '****************' 
     297               WRITE(numout,*) 'prism_get_proto: Incoming ', srcv(kid)%clname 
     298               WRITE(numout,*) 'prism_get_proto: ivarid '  , srcv(kid)%nid(jc) 
     299               WRITE(numout,*) 'prism_get_proto:   kstep', kstep 
     300               WRITE(numout,*) 'prism_get_proto:   info ', kinfo 
     301               WRITE(numout,*) '     - Minimum value is ', MINVAL(pdata(:,:,jc)) 
     302               WRITE(numout,*) '     - Maximum value is ', MAXVAL(pdata(:,:,jc)) 
     303               WRITE(numout,*) '     -     Sum value is ', SUM(pdata(:,:,jc)) 
     304               WRITE(numout,*) '****************' 
     305            ENDIF 
     306             
     307         ELSE 
     308            kinfo = OASIS_idle      
    277309         ENDIF 
    278        
    279       ELSE 
    280          kinfo = OASIS_idle      
    281       ENDIF 
     310          
     311      ENDDO 
    282312      ! 
    283313   END SUBROUTINE cpl_prism_rcv 
  • branches/2011/dev_NOC_UKMO_MERGE/NEMOGCM/NEMO/OPA_SRC/SBC/fldread.F90

    r2777 r3094  
    2424   IMPLICIT NONE 
    2525   PRIVATE    
     26  
     27   PUBLIC   fld_map    ! routine called by tides_init 
    2628 
    2729   TYPE, PUBLIC ::   FLD_N      !: Namelist field informations 
     
    5658      LOGICAL                         ::   rotn         ! flag to indicate whether field has been rotated 
    5759   END TYPE FLD 
     60 
     61   TYPE, PUBLIC ::   MAP_POINTER      !: Array of integer pointers to 1D arrays 
     62      INTEGER, POINTER   ::  ptr(:) 
     63   END TYPE MAP_POINTER 
    5864 
    5965!$AGRIF_DO_NOT_TREAT 
     
    98104CONTAINS 
    99105 
    100    SUBROUTINE fld_read( kt, kn_fsbc, sd ) 
     106   SUBROUTINE fld_read( kt, kn_fsbc, sd, map, jit, time_offset ) 
    101107      !!--------------------------------------------------------------------- 
    102108      !!                    ***  ROUTINE fld_read  *** 
     
    113119      INTEGER  , INTENT(in   )               ::   kn_fsbc   ! sbc computation period (in time step)  
    114120      TYPE(FLD), INTENT(inout), DIMENSION(:) ::   sd        ! input field related variables 
     121      TYPE(MAP_POINTER),INTENT(in), OPTIONAL, DIMENSION(:) ::   map   ! global-to-local mapping index 
     122      INTEGER  , INTENT(in   ), OPTIONAL     ::   jit       ! subcycle timestep for timesplitting option 
     123      INTEGER  , INTENT(in   ), OPTIONAL     ::   time_offset ! provide fields at time other than "now" 
     124                                                              ! time_offset = -1 => fields at "before" time level 
     125                                                              ! time_offset = +1 => fields at "after" time levels 
     126                                                              ! etc. 
    115127      !! 
    116128      INTEGER  ::   imf        ! size of the structure sd 
     
    119131      INTEGER  ::   isecend    ! number of second since Jan. 1st 00h of nit000 year at nitend 
    120132      INTEGER  ::   isecsbc    ! number of seconds between Jan. 1st 00h of nit000 year and the middle of sbc time step 
     133      INTEGER  ::   time_add   ! local time_offset variable 
    121134      LOGICAL  ::   llnxtyr    ! open next year  file? 
    122135      LOGICAL  ::   llnxtmth   ! open next month file? 
    123136      LOGICAL  ::   llstop     ! stop is the file does not exist 
     137      LOGICAL  ::   ll_firstcall ! true if this is the first call to fld_read for this set of fields 
    124138      REAL(wp) ::   ztinta     ! ratio applied to after  records when doing time interpolation 
    125139      REAL(wp) ::   ztintb     ! ratio applied to before records when doing time interpolation 
    126140      CHARACTER(LEN=1000) ::   clfmt   ! write format 
    127141      !!--------------------------------------------------------------------- 
     142      ll_firstcall = .false. 
     143      IF( PRESENT(jit) ) THEN 
     144         IF(kt == nit000 .and. jit == 1) ll_firstcall = .true. 
     145      ELSE 
     146         IF(kt == nit000) ll_firstcall = .true. 
     147      ENDIF 
     148 
     149      time_add = 0 
     150      IF( PRESENT(time_offset) ) THEN 
     151         time_add = time_offset 
     152      ENDIF 
     153          
    128154      ! Note that shifting time to be centrered in the middle of sbc time step impacts only nsec_* variables of the calendar  
    129       isecsbc = nsec_year + nsec1jan000 + NINT(0.5 * REAL(kn_fsbc - 1,wp) * rdttra(1))   ! middle of sbc time step 
     155      IF( present(jit) ) THEN  
     156         ! ignore kn_fsbc in this case 
     157         isecsbc = nsec_year + nsec1jan000 + (jit+time_add)*rdt/REAL(nn_baro,wp)  
     158      ELSE 
     159         isecsbc = nsec_year + nsec1jan000 + NINT(0.5 * REAL(kn_fsbc - 1,wp) * rdttra(1)) + time_add * rdttra(1)  ! middle of sbc time step 
     160      ENDIF 
    130161      imf = SIZE( sd ) 
    131162      ! 
    132       IF( kt == nit000 ) THEN                      ! initialization 
    133          DO jf = 1, imf  
    134             CALL fld_init( kn_fsbc, sd(jf) )       ! read each before field (put them in after as they will be swapped) 
    135          END DO 
     163      IF( ll_firstcall ) THEN                      ! initialization 
     164         IF( PRESENT(map) ) THEN 
     165            DO jf = 1, imf  
     166               CALL fld_init( kn_fsbc, sd(jf), map(jf)%ptr )  ! read each before field (put them in after as they will be swapped) 
     167            END DO 
     168         ELSE 
     169            DO jf = 1, imf  
     170               CALL fld_init( kn_fsbc, sd(jf) )       ! read each before field (put them in after as they will be swapped) 
     171            END DO 
     172         ENDIF 
    136173         IF( lwp ) CALL wgt_print()                ! control print 
    137174         CALL fld_rot( kt, sd )                    ! rotate vector fiels if needed 
     
    143180         DO jf = 1, imf                            ! ---   loop over field   --- ! 
    144181             
    145             IF( isecsbc > sd(jf)%nrec_a(2) .OR. kt == nit000 ) THEN  ! read/update the after data? 
     182            IF( isecsbc > sd(jf)%nrec_a(2) .OR. ll_firstcall ) THEN  ! read/update the after data? 
    146183 
    147184               IF( sd(jf)%ln_tint ) THEN                             ! swap before record field and informations 
     
    151188               ENDIF 
    152189 
    153                CALL fld_rec( kn_fsbc, sd(jf) )                       ! update record informations 
     190               IF( PRESENT(jit) ) THEN 
     191                  CALL fld_rec( kn_fsbc, sd(jf), jit=jit )              ! update record informations 
     192               ELSE 
     193                  CALL fld_rec( kn_fsbc, sd(jf) )                       ! update record informations 
     194               ENDIF 
    154195 
    155196               ! do we have to change the year/month/week/day of the forcing field??  
     
    212253 
    213254               ! read after data 
    214                CALL fld_get( sd(jf) ) 
     255               IF( PRESENT(map) ) THEN 
     256                  CALL fld_get( sd(jf), map(jf)%ptr ) 
     257               ELSE 
     258                  CALL fld_get( sd(jf) ) 
     259               ENDIF 
    215260 
    216261            ENDIF 
     
    225270                  clfmt = "('fld_read: var ', a, ' kt = ', i8, ' (', f7.2,' days), Y/M/D = ', i4.4,'/', i2.2,'/', i2.2," //   & 
    226271                     &    "', records b/a: ', i4.4, '/', i4.4, ' (days ', f7.2,'/', f7.2, ')')" 
    227                   WRITE(numout, clfmt)  TRIM( sd(jf)%clvar ), kt, REAL(isecsbc,wp)/rday, nyear, nmonth, nday,   & 
     272                  WRITE(numout, clfmt)  TRIM( sd(jf)%clvar ), kt, REAL(isecsbc,wp)/rday, nyear, nmonth, nday,   &             
    228273                     & sd(jf)%nrec_b(1), sd(jf)%nrec_a(1), REAL(sd(jf)%nrec_b(2),wp)/rday, REAL(sd(jf)%nrec_a(2),wp)/rday 
     274                  WRITE(numout, *) 'time_add is : ',time_add 
    229275               ENDIF 
    230276               ! temporal interpolation weights 
     
    253299 
    254300 
    255    SUBROUTINE fld_init( kn_fsbc, sdjf ) 
     301   SUBROUTINE fld_init( kn_fsbc, sdjf, map ) 
    256302      !!--------------------------------------------------------------------- 
    257303      !!                    ***  ROUTINE fld_init  *** 
     
    262308      INTEGER  , INTENT(in   ) ::   kn_fsbc   ! sbc computation period (in time step)  
    263309      TYPE(FLD), INTENT(inout) ::   sdjf      ! input field related variables 
     310      INTEGER  , INTENT(in), OPTIONAL, DIMENSION(:) :: map ! global-to-local mapping indices 
    264311      !! 
    265312      LOGICAL :: llprevyr              ! are we reading previous year  file? 
     
    364411 
    365412         ! read before data  
    366          CALL fld_get( sdjf )  ! read before values in after arrays(as we will swap it later) 
     413         IF( PRESENT(map) ) THEN 
     414            CALL fld_get( sdjf, map )  ! read before values in after arrays(as we will swap it later) 
     415         ELSE 
     416            CALL fld_get( sdjf )  ! read before values in after arrays(as we will swap it later) 
     417         ENDIF 
    367418 
    368419         clfmt = "('fld_init : time-interpolation for ', a, ' read previous record = ', i4, ' at time = ', f7.2, ' days')" 
     
    396447 
    397448 
    398    SUBROUTINE fld_rec( kn_fsbc, sdjf, ldbefore ) 
     449   SUBROUTINE fld_rec( kn_fsbc, sdjf, ldbefore, jit ) 
    399450      !!--------------------------------------------------------------------- 
    400451      !!                    ***  ROUTINE fld_rec  *** 
     
    410461      TYPE(FLD), INTENT(inout)           ::   sdjf      ! input field related variables 
    411462      LOGICAL  , INTENT(in   ), OPTIONAL ::   ldbefore  ! sent back before record values (default = .FALSE.) 
     463      INTEGER  , INTENT(in   ), OPTIONAL ::   jit       ! index of barotropic subcycle 
    412464                                                        ! used only if sdjf%ln_tint = .TRUE. 
    413465      !! 
     
    443495            !                             
    444496            ztmp = REAL( nday, wp ) / REAL( nyear_len(1), wp ) + 0.5 
     497            IF( PRESENT(jit) ) ztmp = ztmp + jit*rdt/REAL(nn_baro,wp) 
    445498            sdjf%nrec_a(1) = 1 + INT( ztmp ) - COUNT((/llbefore/)) 
    446499            ! swap at the middle of the year 
     
    471524            !                             
    472525            ztmp = REAL( nday, wp ) / REAL( nmonth_len(nmonth), wp ) + 0.5 
     526            IF( PRESENT(jit) ) ztmp = ztmp + jit*rdt/REAL(nn_baro,wp) 
    473527            imth = nmonth + INT( ztmp ) - COUNT((/llbefore/)) 
    474528            IF( sdjf%cltype == 'monthly' ) THEN   ;   sdjf%nrec_a(1) = 1 + INT( ztmp ) - COUNT((/llbefore/)) 
     
    498552         ztmp = ztmp + 0.5 * REAL(kn_fsbc - 1, wp) * rdttra(1)   ! shift time to be centrered in the middle of sbc time step 
    499553         ztmp = ztmp + 0.01 * rdttra(1)                          ! add 0.01 time step to avoid truncation error  
     554         IF( PRESENT(jit) ) ztmp = ztmp + jit*rdt/REAL(nn_baro,wp) 
    500555         IF( sdjf%ln_tint ) THEN                ! time interpolation, shift by 1/2 record 
    501556            ! 
     
    546601 
    547602 
    548    SUBROUTINE fld_get( sdjf ) 
    549       !!--------------------------------------------------------------------- 
    550       !!                    ***  ROUTINE fld_clopn  *** 
     603   SUBROUTINE fld_get( sdjf, map ) 
     604      !!--------------------------------------------------------------------- 
     605      !!                    ***  ROUTINE fld_get  *** 
    551606      !! 
    552607      !! ** Purpose :   read the data 
    553608      !!---------------------------------------------------------------------- 
    554609      TYPE(FLD), INTENT(inout) ::   sdjf   ! input field related variables 
     610      INTEGER  , INTENT(in), OPTIONAL, DIMENSION(:) :: map ! global-to-local mapping indices 
    555611      !! 
    556612      INTEGER                  ::   ipk    ! number of vertical levels of sdjf%fdta ( 2D: ipk=1 ; 3D: ipk=jpk ) 
     
    559615             
    560616      ipk = SIZE( sdjf%fnow, 3 ) 
    561       IF( LEN(TRIM(sdjf%wgtname)) > 0 ) THEN 
     617 
     618      IF( PRESENT(map) ) THEN 
     619         IF( sdjf%ln_tint ) THEN   ;   CALL fld_map( sdjf%num, sdjf%clvar, sdjf%fdta(:,:,:,2), sdjf%nrec_a(1), map ) 
     620         ELSE                      ;   CALL fld_map( sdjf%num, sdjf%clvar, sdjf%fnow(:,:,:  ), sdjf%nrec_a(1), map ) 
     621         ENDIF 
     622      ELSE IF( LEN(TRIM(sdjf%wgtname)) > 0 ) THEN 
    562623         CALL wgt_list( sdjf, iw ) 
    563624         IF( sdjf%ln_tint ) THEN   ;   CALL fld_interp( sdjf%num, sdjf%clvar, iw , ipk  , sdjf%fdta(:,:,:,2), sdjf%nrec_a(1) ) 
     
    581642   END SUBROUTINE fld_get 
    582643 
     644   SUBROUTINE fld_map( num, clvar, dta, nrec, map ) 
     645      !!--------------------------------------------------------------------- 
     646      !!                    ***  ROUTINE fld_get  *** 
     647      !! 
     648      !! ** Purpose :   read global data from file and map onto local data 
     649      !!                using a general mapping (for open boundaries) 
     650      !!---------------------------------------------------------------------- 
     651#if defined key_bdy 
     652      USE bdy_oce, ONLY:  dta_global         ! workspace to read in global data arrays 
     653#endif  
     654 
     655      INTEGER                   , INTENT(in ) ::   num     ! stream number 
     656      CHARACTER(LEN=*)          , INTENT(in ) ::   clvar   ! variable name 
     657      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   dta   ! output field on model grid (2 dimensional) 
     658      INTEGER                   , INTENT(in ) ::   nrec    ! record number to read (ie time slice) 
     659      INTEGER,  DIMENSION(:)    , INTENT(in ) ::   map     ! global-to-local mapping indices 
     660      !! 
     661      INTEGER                                 ::   ipi      ! length of boundary data on local process 
     662      INTEGER                                 ::   ipj      ! length of dummy dimension ( = 1 ) 
     663      INTEGER                                 ::   ipk      ! number of vertical levels of dta ( 2D: ipk=1 ; 3D: ipk=jpk ) 
     664      INTEGER                                 ::   ilendta  ! length of data in file 
     665      INTEGER                                 ::   idvar    ! variable ID 
     666      INTEGER                                 ::   ib, ik   ! loop counters 
     667      INTEGER                                 ::   ierr 
     668      REAL(wp), POINTER, DIMENSION(:,:,:)     ::   dta_read ! work space for global data 
     669      !!--------------------------------------------------------------------- 
     670             
     671#if defined key_bdy 
     672      dta_read => dta_global 
     673#endif 
     674 
     675      ipi = SIZE( dta, 1 ) 
     676      ipj = 1 
     677      ipk = SIZE( dta, 3 ) 
     678 
     679      idvar   = iom_varid( num, clvar ) 
     680      ilendta = iom_file(num)%dimsz(1,idvar) 
     681      IF(lwp) WRITE(numout,*) 'Dim size for ',TRIM(clvar),' is ', ilendta 
     682      IF(lwp) WRITE(numout,*) 'Number of levels for ',TRIM(clvar),' is ', ipk 
     683 
     684      SELECT CASE( ipk ) 
     685      CASE(1)    
     686         CALL iom_get ( num, jpdom_unknown, clvar, dta_read(1:ilendta,1:ipj,1    ), nrec ) 
     687      CASE DEFAULT 
     688         CALL iom_get ( num, jpdom_unknown, clvar, dta_read(1:ilendta,1:ipj,1:ipk), nrec ) 
     689      END SELECT 
     690      ! 
     691      DO ib = 1, ipi 
     692         DO ik = 1, ipk 
     693            dta(ib,1,ik) =  dta_read(map(ib),1,ik) 
     694         END DO 
     695      END DO 
     696 
     697   END SUBROUTINE fld_map 
     698 
    583699 
    584700   SUBROUTINE fld_rot( kt, sd ) 
    585701      !!--------------------------------------------------------------------- 
    586       !!                    ***  ROUTINE fld_clopn  *** 
     702      !!                    ***  ROUTINE fld_rot  *** 
    587703      !! 
    588704      !! ** Purpose :   Vector fields may need to be rotated onto the local grid direction 
    589705      !!---------------------------------------------------------------------- 
    590706      USE wrk_nemo, ONLY: wrk_in_use, wrk_not_released 
    591       USE wrk_nemo, ONLY: utmp => wrk_2d_4, vtmp => wrk_2d_5      ! 2D workspace 
     707      USE wrk_nemo, ONLY: utmp => wrk_2d_24, vtmp => wrk_2d_25      ! 2D workspace 
    592708      !! 
    593709      INTEGER  , INTENT(in   )               ::   kt        ! ocean time step 
     
    601717      !!--------------------------------------------------------------------- 
    602718 
    603       IF(wrk_in_use(2, 4,5) ) THEN 
     719      IF(wrk_in_use(2, 24,25) ) THEN 
    604720         CALL ctl_stop('fld_rot: ERROR: requested workspace arrays are unavailable.')   ;   RETURN 
    605721      END IF 
     
    638754       END DO 
    639755      ! 
    640       IF(wrk_not_released(2, 4,5) )    CALL ctl_stop('fld_rot: ERROR: failed to release workspace arrays.') 
     756      IF(wrk_not_released(2, 24,25) )    CALL ctl_stop('fld_rot: ERROR: failed to release workspace arrays.') 
    641757      ! 
    642758   END SUBROUTINE fld_rot 
     
    672788      ! 
    673789      CALL iom_open( sdjf%clname, sdjf%num, ldstop = ldstop, ldiof =  LEN(TRIM(sdjf%wgtname)) > 0 ) 
    674       ! 
     790     ! 
    675791   END SUBROUTINE fld_clopn 
    676792 
  • branches/2011/dev_NOC_UKMO_MERGE/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_ice.F90

    r2777 r3094  
    66   !! History :  3.0  ! 2006-08  (G. Madec)  Surface module 
    77   !!            3.2  ! 2009-06  (S. Masson) merge with ice_oce 
    8    !!            4.0  ! 2011-01  (A. R. Porter, STFC Daresbury) dynamical allocation 
     8   !!            3.3.1! 2011-01  (A. R. Porter, STFC Daresbury) dynamical allocation 
     9   !!            3.4  ! 2011-11  (C. Harris) CICE added as an option 
    910   !!---------------------------------------------------------------------- 
    10 #if defined key_lim3 || defined key_lim2 
     11#if defined key_lim3 || defined key_lim2 || defined key_cice 
    1112   !!---------------------------------------------------------------------- 
    1213   !!   'key_lim2' or 'key_lim3' :             LIM-2 or LIM-3 sea-ice model 
     
    1920   USE par_ice_2        ! LIM-2 parameters 
    2021# endif 
     22# if defined key_cice  
     23   USE ice_domain_size, only: ncat  
     24#endif 
    2125   USE lib_mpp          ! MPP library 
    2226   USE in_out_manager   ! I/O manager 
     
    3034   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .TRUE.   !: LIM-2 ice model 
    3135   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .FALSE.  !: no LIM-3 
     36   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE  
    3237#  if defined key_lim2_vp 
    3338   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = 'I'      !: VP : 'I'-grid ice-velocity (B-grid lower left corner) 
     
    3944   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .FALSE.  !: no LIM-2 
    4045   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .TRUE.   !: LIM-3 ice model 
     46   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE  
    4147   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = 'C'      !: 'C'-grid ice-velocity 
    4248# endif 
     49# if defined  key_cice 
     50   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .FALSE.  !: no LIM-2 
     51   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .FALSE.  !: no LIM-3 
     52   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .TRUE.   !: CICE ice model 
     53   CHARACTER(len=1), PUBLIC            ::   cp_ice_msh = 'F'      !: 'F'-grid ice-velocity 
     54# endif 
    4355 
     56#if defined key_lim3 || defined key_lim2  
    4457   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qns_ice   !: non solar heat flux over ice                  [W/m2] 
    4558   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice   !: solar heat flux over ice                      [W/m2] 
     
    6073# endif 
    6174 
     75#elif defined key_cice 
     76   ! 
     77   ! for consistency with LIM, these are declared with three dimensions 
     78   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qlw_ice            !: incoming long-wave 
     79   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qla_ice            !: latent flux over ice           [W/m2] 
     80   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice            !: solar heat flux over ice       [W/m2] 
     81   ! 
     82   ! other forcing arrays are two dimensional 
     83   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ss_iou             !: x ice-ocean surface stress at NEMO U point 
     84   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ss_iov             !: y ice-ocean surface stress at NEMO V point 
     85   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   emp_ice            !: sublimation-snow budget over ice    [kg/m2] 
     86   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   tatm_ice           !: air temperature 
     87   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qatm_ice           !: specific humidity 
     88   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wndi_ice           !: i wind at T point 
     89   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wndj_ice           !: j wind at T point 
     90   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nfrzmlt            !: NEMO frzmlt 
     91   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iu              !: ice fraction at NEMO U point 
     92   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iv              !: ice fraction at NEMO V point 
     93   ! 
     94   ! finally, arrays corresponding to different ice categories 
     95   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_i                !: category ice fraction 
     96   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   topmelt           !: category topmelt 
     97   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   botmelt           !: category botmelt 
     98#endif 
     99 
    62100   !!---------------------------------------------------------------------- 
    63101   !! NEMO/OPA 4.0 , NEMO Consortium (2011) 
     
    71109      !!                     ***  FUNCTION sbc_ice_alloc  *** 
    72110      !!---------------------------------------------------------------------- 
     111#if defined key_lim3 || defined key_lim2 
    73112      ALLOCATE( qns_ice (jpi,jpj,jpl) , qsr_ice (jpi,jpj,jpl) ,     & 
    74113         &      qla_ice (jpi,jpj,jpl) , dqla_ice(jpi,jpj,jpl) ,     & 
     
    77116         &      utau_ice(jpi,jpj)     , vtau_ice(jpi,jpj)     ,     & 
    78117         &      fr1_i0  (jpi,jpj)     , fr2_i0  (jpi,jpj)     ,     & 
    79 # if defined key_lim3 
     118#if defined key_lim3 
    80119         &      emp_ice(jpi,jpj)      , tatm_ice(jpi,jpj)     , STAT= sbc_ice_alloc ) 
    81 # else 
     120#else 
    82121         &      emp_ice(jpi,jpj)                              , STAT= sbc_ice_alloc ) 
    83 # endif 
     122#endif 
     123#elif defined key_cice 
     124      ALLOCATE( qla_ice(jpi,jpj,1)    , qlw_ice(jpi,jpj,1)    , qsr_ice(jpi,jpj,1)    , & 
     125                wndi_ice(jpi,jpj)     , tatm_ice(jpi,jpj)     , qatm_ice(jpi,jpj)     , & 
     126                wndj_ice(jpi,jpj)     , nfrzmlt(jpi,jpj)      , ss_iou(jpi,jpj)       , & 
     127                ss_iov(jpi,jpj)       , fr_iu(jpi,jpj)        , fr_iv(jpi,jpj)        , & 
     128                a_i(jpi,jpj,ncat)     , topmelt(jpi,jpj,ncat) , botmelt(jpi,jpj,ncat), STAT= sbc_ice_alloc ) 
     129#endif 
    84130         ! 
    85131      IF( lk_mpp            )   CALL mpp_sum ( sbc_ice_alloc ) 
     
    89135#else 
    90136   !!---------------------------------------------------------------------- 
    91    !!   Default option                      NO LIM 2.0 or 3.0 sea-ice model 
     137   !!   Default option                      NO LIM 2.0 or 3.0 or CICE sea-ice model 
    92138   !!---------------------------------------------------------------------- 
    93139   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim2    = .FALSE.  !: no LIM-2 ice model 
    94140   LOGICAL         , PUBLIC, PARAMETER ::   lk_lim3    = .FALSE.  !: no LIM-3 ice model 
     141   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE  ice model 
    95142   CHARACTER(len=1), PUBLIC, PARAMETER ::   cp_ice_msh = '-'      !: no grid ice-velocity 
    96143#endif 
  • branches/2011/dev_NOC_UKMO_MERGE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcapr.F90

    r2715 r3094  
    1010   !!   sbc_apr        : read atmospheric pressure in netcdf files  
    1111   !!---------------------------------------------------------------------- 
    12    USE bdy_par         ! Unstructured boundary parameters 
    1312   USE obc_par         ! open boundary condition parameters 
    1413   USE dom_oce         ! ocean space and time domain 
     
    3029   !                                         !!* namsbc_apr namelist (Atmospheric PRessure) * 
    3130   LOGICAL, PUBLIC ::   ln_apr_obc = .FALSE.  !: inverse barometer added to OBC ssh data  
    32    LOGICAL, PUBLIC ::   ln_apr_bdy = .FALSE.  !: inverse barometer added to BDY ssh data 
    3331   LOGICAL, PUBLIC ::   ln_ref_apr = .FALSE.  !: ref. pressure: global mean Patm (F) or a constant (F) 
    3432 
     
    115113         ! 
    116114         !                                            !* control check 
    117          IF( ln_apr_obc .OR. ln_apr_bdy  )   & 
    118             CALL ctl_stop( 'sbc_apr: inverse barometer added to OBC or BDY ssh data not yet implemented ' ) 
     115         IF( ln_apr_obc )   & 
     116            CALL ctl_stop( 'sbc_apr: inverse barometer added to OBC ssh data not yet implemented ' ) 
    119117         IF( ln_apr_obc .AND. .NOT. lk_obc )   & 
    120118            CALL ctl_stop( 'sbc_apr: add inverse barometer to OBC requires to use key_obc' ) 
    121          IF( ln_apr_bdy .AND. .NOT. lk_bdy )   & 
    122             CALL ctl_stop( 'sbc_apr: add inverse barometer to OBC requires to use key_bdy' ) 
    123          IF( ( ln_apr_obc .OR. ln_apr_bdy ) .AND. .NOT. lk_dynspg_ts )   & 
     119         IF( ( ln_apr_obc ) .AND. .NOT. lk_dynspg_ts )   & 
    124120            CALL ctl_stop( 'sbc_apr: use inverse barometer ssh at open boundary ONLY possible with time-splitting' ) 
    125          IF( ( ln_apr_obc .OR. ln_apr_bdy ) .AND. .NOT. ln_apr_dyn   )   & 
     121         IF( ( ln_apr_obc ) .AND. .NOT. ln_apr_dyn   )   & 
    126122            CALL ctl_stop( 'sbc_apr: use inverse barometer ssh at open boundary ONLY requires ln_apr_dyn=T' ) 
    127123      ENDIF 
  • branches/2011/dev_NOC_UKMO_MERGE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_core.F90

    r2777 r3094  
    1414   !!            3.2  !  2009-04  (B. Lemaire)  Introduce iom_put 
    1515   !!            3.3  !  2010-10  (S. Masson)  add diurnal cycle 
     16   !!            3.4  !  2011-11  (C. Harris) Fill arrays required by CICE 
    1617   !!---------------------------------------------------------------------- 
    1718 
     
    3435   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    3536   USE prtctl          ! Print control 
    36 #if defined key_lim3 
     37#if defined key_lim3 || defined key_cice 
    3738   USE sbc_ice         ! Surface boundary condition: ice fields 
    3839#endif 
     
    182183      !                                                        ! surface ocean fluxes computed with CLIO bulk formulea 
    183184      IF( MOD( kt - 1, nn_fsbc ) == 0 )   CALL blk_oce_core( sf, sst_m, ssu_m, ssv_m ) 
     185 
     186#if defined key_cice 
     187      IF( MOD( kt - 1, nn_fsbc ) == 0 )   THEN 
     188         qlw_ice(:,:,1)   = sf(jp_qlw)%fnow(:,:,1)  
     189         qsr_ice(:,:,1)   = sf(jp_qsr)%fnow(:,:,1) 
     190         tatm_ice(:,:)    = sf(jp_tair)%fnow(:,:,1)          
     191         qatm_ice(:,:)    = sf(jp_humi)%fnow(:,:,1) 
     192         tprecip(:,:)     = sf(jp_prec)%fnow(:,:,1) * rn_pfac 
     193         sprecip(:,:)     = sf(jp_snow)%fnow(:,:,1) * rn_pfac 
     194         wndi_ice(:,:)    = sf(jp_wndi)%fnow(:,:,1) 
     195         wndj_ice(:,:)    = sf(jp_wndj)%fnow(:,:,1) 
     196      ENDIF 
     197#endif 
    184198      ! 
    185199   END SUBROUTINE sbc_blk_core 
  • branches/2011/dev_NOC_UKMO_MERGE/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r2715 r3094  
    77   !!            3.0  ! 2008-02  (G. Madec, C Talandier)  surface module 
    88   !!            3.1  ! 2009_02  (G. Madec, S. Masson, E. Maisonave, A. Caubel) generic coupled interface 
     9   !!            3.4  ! 2011_11  (C. Harris) more flexibility + multi-category fields 
    910   !!---------------------------------------------------------------------- 
    1011#if defined key_oasis3 || defined key_oasis4 
     
    4142   USE geo2ocean       !  
    4243   USE restart         ! 
    43    USE oce   , ONLY : tn, un, vn 
     44   USE oce   , ONLY : tsn, un, vn 
    4445   USE albedo          ! 
    4546   USE in_out_manager  ! I/O manager 
     
    5152#endif 
    5253   USE diaar5, ONLY :   lk_diaar5 
     54#if defined key_cice 
     55   USE ice_domain_size, only: ncat 
     56#endif 
    5357   IMPLICIT NONE 
    5458   PRIVATE 
     
    8993   INTEGER, PARAMETER ::   jpr_cal    = 29            ! calving 
    9094   INTEGER, PARAMETER ::   jpr_taum   = 30            ! wind stress module 
    91 #if ! defined key_cpl_carbon_cycle 
    92    INTEGER, PARAMETER ::   jprcv      = 30            ! total number of fields received 
    93 #else 
    9495   INTEGER, PARAMETER ::   jpr_co2    = 31 
    95    INTEGER, PARAMETER ::   jprcv      = 31            ! total number of fields received 
    96 #endif    
     96   INTEGER, PARAMETER ::   jpr_topm   = 32            ! topmeltn 
     97   INTEGER, PARAMETER ::   jpr_botm   = 33            ! botmeltn 
     98   INTEGER, PARAMETER ::   jprcv      = 33            ! total number of fields received 
     99 
    97100   INTEGER, PARAMETER ::   jps_fice   =  1            ! ice fraction  
    98101   INTEGER, PARAMETER ::   jps_toce   =  2            ! ocean temperature 
     
    109112   INTEGER, PARAMETER ::   jps_ivy1   = 13            ! 
    110113   INTEGER, PARAMETER ::   jps_ivz1   = 14            ! 
    111 #if ! defined key_cpl_carbon_cycle 
    112    INTEGER, PARAMETER ::   jpsnd      = 14            ! total number of fields sended 
    113 #else 
    114114   INTEGER, PARAMETER ::   jps_co2    = 15 
    115115   INTEGER, PARAMETER ::   jpsnd      = 15            ! total number of fields sended 
    116 #endif    
     116 
    117117   !                                                         !!** namelist namsbc_cpl ** 
    118    ! Send to the atmosphere                                   ! 
    119    CHARACTER(len=100) ::   cn_snd_temperature = 'oce only'    ! 'oce only' 'weighted oce and ice' or 'mixed oce-ice' 
    120    CHARACTER(len=100) ::   cn_snd_albedo      = 'none'        ! 'none' 'weighted ice' or 'mixed oce-ice' 
    121    CHARACTER(len=100) ::   cn_snd_thickness   = 'none'        ! 'none' or 'weighted ice and snow' 
    122    CHARACTER(len=100) ::   cn_snd_crt_nature  = 'none'        ! 'none' 'oce only' 'weighted oce and ice' or 'mixed oce-ice'    
    123    CHARACTER(len=100) ::   cn_snd_crt_refere  = 'spherical'   ! 'spherical' or 'cartesian' 
    124    CHARACTER(len=100) ::   cn_snd_crt_orient  = 'local grid'  ! 'eastward-northward' or 'local grid' 
    125    CHARACTER(len=100) ::   cn_snd_crt_grid    = 'T'           ! always at 'T' point 
    126 #if defined key_cpl_carbon_cycle  
    127    CHARACTER(len=100) ::   cn_snd_co2         = 'none'        ! 'none' or 'coupled' 
     118   TYPE ::   FLD_C 
     119      CHARACTER(len = 32) ::   cldes                  ! desciption of the coupling strategy 
     120      CHARACTER(len = 32) ::   clcat                  ! multiple ice categories strategy 
     121      CHARACTER(len = 32) ::   clvref                 ! reference of vector ('spherical' or 'cartesian') 
     122      CHARACTER(len = 32) ::   clvor                  ! orientation of vector fields ('eastward-northward' or 'local grid') 
     123      CHARACTER(len = 32) ::   clvgrd                 ! grids on which is located the vector fields 
     124   END TYPE FLD_C 
     125   ! Send to the atmosphere                           ! 
     126   TYPE(FLD_C) ::   sn_snd_temp, sn_snd_alb, sn_snd_thick, sn_snd_crt, sn_snd_co2                         
     127   ! Received from the atmosphere                     ! 
     128   TYPE(FLD_C) ::   sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau, sn_rcv_dqnsdt, sn_rcv_qsr, sn_rcv_qns, sn_rcv_emp, sn_rcv_rnf 
     129   TYPE(FLD_C) ::   sn_rcv_cal, sn_rcv_iceflx, sn_rcv_co2                         
     130 
     131   TYPE ::   DYNARR      
     132      REAL(wp), POINTER, DIMENSION(:,:,:)    ::   z3    
     133   END TYPE DYNARR 
     134 
     135   TYPE( DYNARR ), SAVE, DIMENSION(jprcv) ::   frcv                      ! all fields recieved from the atmosphere 
     136 
     137   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   albedo_oce_mix     ! ocean albedo sent to atmosphere (mix clear/overcast sky) 
     138 
     139   INTEGER , ALLOCATABLE, SAVE, DIMENSION(    :) ::   nrcvinfo           ! OASIS info argument 
     140 
     141#if ! defined key_lim2   &&   ! defined key_lim3 
     142   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   u_ice, v_ice,fr1_i0,fr2_i0          ! jpi, jpj 
     143   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tn_ice, alb_ice, qns_ice, dqns_ice  ! (jpi,jpj,jpl) 
    128144#endif 
    129    ! Received from the atmosphere                             ! 
    130    CHARACTER(len=100) ::   cn_rcv_tau_nature  = 'oce only'    ! 'oce only' 'oce and ice' or 'mixed oce-ice' 
    131    CHARACTER(len=100) ::   cn_rcv_tau_refere  = 'spherical'   ! 'spherical' or 'cartesian' 
    132    CHARACTER(len=100) ::   cn_rcv_tau_orient  = 'local grid'  ! 'eastward-northward' or 'local grid' 
    133    CHARACTER(len=100) ::   cn_rcv_tau_grid    = 'T'           ! 'T', 'U,V', 'U,V,I', 'T,I', or 'T,U,V' 
    134    CHARACTER(len=100) ::   cn_rcv_w10m        = 'none'        ! 'none' or 'coupled' 
    135    CHARACTER(len=100) ::   cn_rcv_dqnsdt      = 'none'        ! 'none' or 'coupled' 
    136    CHARACTER(len=100) ::   cn_rcv_qsr         = 'oce only'    ! 'oce only' 'conservative' 'oce and ice' or 'mixed oce-ice' 
    137    CHARACTER(len=100) ::   cn_rcv_qns         = 'oce only'    ! 'oce only' 'conservative' 'oce and ice' or 'mixed oce-ice' 
    138    CHARACTER(len=100) ::   cn_rcv_emp         = 'oce only'    ! 'oce only' 'conservative' or 'oce and ice' 
    139    CHARACTER(len=100) ::   cn_rcv_rnf         = 'coupled'     ! 'coupled' 'climato' or 'mixed' 
    140    CHARACTER(len=100) ::   cn_rcv_cal         = 'none'        ! 'none' or 'coupled' 
    141    CHARACTER(len=100) ::   cn_rcv_taumod      = 'none'        ! 'none' or 'coupled' 
    142 #if defined key_cpl_carbon_cycle  
    143    CHARACTER(len=100) ::   cn_rcv_co2         = 'none'        ! 'none' or 'coupled' 
     145 
     146#if defined key_cice 
     147   INTEGER, PARAMETER ::   jpl = ncat 
     148#elif ! defined key_lim2   &&   ! defined key_lim3 
     149   INTEGER, PARAMETER ::   jpl = 1  
     150   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   emp_ice 
     151   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice 
    144152#endif 
    145153 
    146 !!   CHARACTER(len=100), PUBLIC ::   cn_rcv_rnf   !: ???             ==>>  !!gm   treat this case in a different maner 
    147     
    148    CHARACTER(len=100), DIMENSION(4) ::   cn_snd_crt           ! array combining cn_snd_crt_* 
    149    CHARACTER(len=100), DIMENSION(4) ::   cn_rcv_tau           ! array combining cn_rcv_tau_* 
    150  
    151    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   albedo_oce_mix     ! ocean albedo sent to atmosphere (mix clear/overcast sky) 
    152  
    153    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   frcv               ! all fields recieved from the atmosphere 
    154    INTEGER , ALLOCATABLE, SAVE, DIMENSION(    :) ::   nrcvinfo           ! OASIS info argument 
    155  
    156 #if ! defined key_lim2   &&   ! defined key_lim3 
    157    ! quick patch to be able to run the coupled model without sea-ice... 
    158    INTEGER, PARAMETER ::   jpl = 1  
    159    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hicif, hsnif, u_ice, v_ice,fr1_i0,fr2_i0 ! jpi, jpj 
    160    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tn_ice, alb_ice ! (jpi,jpj,jpl) 
    161    REAL(wp) ::  lfus 
     154#if ! defined key_lim3   &&  ! defined key_cice 
     155   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  a_i 
     156#endif 
     157 
     158#if ! defined key_lim3 
     159   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  ht_i, ht_s 
     160#endif 
     161 
     162#if ! defined key_cice 
     163   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  topmelt, botmelt 
    162164#endif 
    163165 
     
    176178      !!             ***  FUNCTION sbc_cpl_alloc  *** 
    177179      !!---------------------------------------------------------------------- 
    178       INTEGER :: ierr(2) 
     180      INTEGER :: ierr(4),jn 
    179181      !!---------------------------------------------------------------------- 
    180182      ierr(:) = 0 
    181183      ! 
    182       ALLOCATE( albedo_oce_mix(jpi,jpj), frcv(jpi,jpj,jprcv), nrcvinfo(jprcv),  STAT=ierr(1) ) 
     184      ALLOCATE( albedo_oce_mix(jpi,jpj), nrcvinfo(jprcv),  STAT=ierr(1) ) 
    183185      ! 
    184186#if ! defined key_lim2 && ! defined key_lim3 
    185187      ! quick patch to be able to run the coupled model without sea-ice... 
    186       ALLOCATE( hicif(jpi,jpj) , u_ice(jpi,jpj) , fr1_i0(jpi,jpj) , tn_ice (jpi,jpj,jpl) ,     & 
    187                 hsnif(jpi,jpj) , v_ice(jpi,jpj) , fr2_i0(jpi,jpj) , alb_ice(jpi,jpj,jpl) , STAT=ierr(2) ) 
     188      ALLOCATE( u_ice(jpi,jpj) , fr1_i0(jpi,jpj) , tn_ice (jpi,jpj,1) ,     & 
     189                v_ice(jpi,jpj) , fr2_i0(jpi,jpj) , alb_ice(jpi,jpj,1),      & 
     190                emp_ice(jpi,jpj) , qns_ice(jpi,jpj,1) , dqns_ice(jpi,jpj,1) , STAT=ierr(2) ) 
     191#endif 
     192 
     193#if ! defined key_lim3 && ! defined key_cice 
     194      ALLOCATE( a_i(jpi,jpj,jpl) , STAT=ierr(3) ) 
     195#endif 
     196 
     197#if defined key_cice || defined key_lim2 
     198      ALLOCATE( ht_i(jpi,jpj,jpl) , ht_s(jpi,jpj,jpl) , STAT=ierr(4) ) 
    188199#endif 
    189200      sbc_cpl_alloc = MAXVAL( ierr ) 
     
    213224      INTEGER ::   jn   ! dummy loop index 
    214225      !! 
    215       NAMELIST/namsbc_cpl/  cn_snd_temperature, cn_snd_albedo    , cn_snd_thickness,                 &           
    216          cn_snd_crt_nature, cn_snd_crt_refere , cn_snd_crt_orient, cn_snd_crt_grid ,                 & 
    217          cn_rcv_w10m      , cn_rcv_taumod     ,                                                      & 
    218          cn_rcv_tau_nature, cn_rcv_tau_refere , cn_rcv_tau_orient, cn_rcv_tau_grid ,                 & 
    219          cn_rcv_dqnsdt    , cn_rcv_qsr        , cn_rcv_qns       , cn_rcv_emp      , cn_rcv_rnf , cn_rcv_cal 
    220 #if defined key_cpl_carbon_cycle  
    221       NAMELIST/namsbc_cpl_co2/  cn_snd_co2, cn_rcv_co2 
    222 #endif 
     226      NAMELIST/namsbc_cpl/  sn_snd_temp, sn_snd_alb   , sn_snd_thick, sn_snd_crt   , sn_snd_co2,   & 
     227         &                  sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau  , sn_rcv_dqnsdt, sn_rcv_qsr,   & 
     228         &                  sn_rcv_qns , sn_rcv_emp   , sn_rcv_rnf  , sn_rcv_cal   , sn_rcv_iceflx  , sn_rcv_co2 
    223229      !!--------------------------------------------------------------------- 
    224230 
     
    230236      !      Namelist informations       ! 
    231237      ! ================================ ! 
     238 
     239      ! default definitions 
     240      !                    !     description       !  multiple  !    vector   !      vector          ! vector ! 
     241      !                    !                       ! categories !  reference  !    orientation       ! grids  ! 
     242      ! send 
     243      sn_snd_temp   = FLD_C( 'weighted oce and ice',    'no'    ,     ''      ,         ''           ,   ''   )  
     244      sn_snd_alb    = FLD_C( 'weighted ice'        ,    'no'    ,     ''      ,         ''           ,   ''   )  
     245      sn_snd_thick  = FLD_C( 'none'                ,    'no'    ,     ''      ,         ''           ,   ''   )  
     246      sn_snd_crt    = FLD_C( 'none'                ,    'no'    , 'spherical' , 'eastward-northward' ,  'T'   )      
     247      sn_snd_co2    = FLD_C( 'none'                ,    'no'    ,     ''      ,         ''           ,   ''   )      
     248      ! receive 
     249      sn_rcv_w10m   = FLD_C( 'none'                ,    'no'    ,     ''      ,         ''          ,   ''    ) 
     250      sn_rcv_taumod = FLD_C( 'coupled'             ,    'no'    ,     ''      ,         ''          ,   ''    ) 
     251      sn_rcv_tau    = FLD_C( 'oce only'            ,    'no'    , 'cartesian' , 'eastward-northward',  'U,V'  )   
     252      sn_rcv_dqnsdt = FLD_C( 'coupled'             ,    'no'    ,     ''      ,         ''          ,   ''    ) 
     253      sn_rcv_qsr    = FLD_C( 'oce and ice'         ,    'no'    ,     ''      ,         ''          ,   ''    ) 
     254      sn_rcv_qns    = FLD_C( 'oce and ice'         ,    'no'    ,     ''      ,         ''          ,   ''    ) 
     255      sn_rcv_emp    = FLD_C( 'conservative'        ,    'no'    ,     ''      ,         ''          ,   ''    ) 
     256      sn_rcv_rnf    = FLD_C( 'coupled'             ,    'no'    ,     ''      ,         ''          ,   ''    ) 
     257      sn_rcv_cal    = FLD_C( 'coupled'             ,    'no'    ,     ''      ,         ''          ,   ''    ) 
     258      sn_rcv_iceflx = FLD_C( 'none'                ,    'no'    ,     ''      ,         ''          ,   ''    ) 
     259      sn_rcv_co2    = FLD_C( 'none'                ,    'no'    ,     ''      ,         ''          ,   ''    ) 
    232260 
    233261      REWIND( numnam )                    ! ... read namlist namsbc_cpl 
     
    238266         WRITE(numout,*)'sbc_cpl_init : namsbc_cpl namelist ' 
    239267         WRITE(numout,*)'~~~~~~~~~~~~' 
    240          WRITE(numout,*)'   received fields' 
    241          WRITE(numout,*)'       10m wind module                    cn_rcv_w10m        = ', cn_rcv_w10m  
    242          WRITE(numout,*)'       surface stress - nature            cn_rcv_tau_nature  = ', cn_rcv_tau_nature 
    243          WRITE(numout,*)'                      - referential       cn_rcv_tau_refere  = ', cn_rcv_tau_refere 
    244          WRITE(numout,*)'                      - orientation       cn_rcv_tau_orient  = ', cn_rcv_tau_orient 
    245          WRITE(numout,*)'                      - mesh              cn_rcv_tau_grid    = ', cn_rcv_tau_grid 
    246          WRITE(numout,*)'       non-solar heat flux sensitivity    cn_rcv_dqnsdt      = ', cn_rcv_dqnsdt 
    247          WRITE(numout,*)'       solar heat flux                    cn_rcv_qsr         = ', cn_rcv_qsr   
    248          WRITE(numout,*)'       non-solar heat flux                cn_rcv_qns         = ', cn_rcv_qns 
    249          WRITE(numout,*)'       freshwater budget                  cn_rcv_emp         = ', cn_rcv_emp 
    250          WRITE(numout,*)'       runoffs                            cn_rcv_rnf         = ', cn_rcv_rnf 
    251          WRITE(numout,*)'       calving                            cn_rcv_cal         = ', cn_rcv_cal  
    252          WRITE(numout,*)'       stress module                      cn_rcv_taumod      = ', cn_rcv_taumod 
    253          WRITE(numout,*)'   sent fields' 
    254          WRITE(numout,*)'       surface temperature                cn_snd_temperature = ', cn_snd_temperature 
    255          WRITE(numout,*)'       albedo                             cn_snd_albedo      = ', cn_snd_albedo 
    256          WRITE(numout,*)'       ice/snow thickness                 cn_snd_thickness   = ', cn_snd_thickness   
    257          WRITE(numout,*)'       surface current - nature           cn_snd_crt_nature  = ', cn_snd_crt_nature  
    258          WRITE(numout,*)'                       - referential      cn_snd_crt_refere  = ', cn_snd_crt_refere  
    259          WRITE(numout,*)'                       - orientation      cn_snd_crt_orient  = ', cn_snd_crt_orient 
    260          WRITE(numout,*)'                       - mesh             cn_snd_crt_grid    = ', cn_snd_crt_grid  
    261       ENDIF 
    262  
    263 #if defined key_cpl_carbon_cycle  
    264       REWIND( numnam )                    ! read namlist namsbc_cpl_co2 
    265       READ  ( numnam, namsbc_cpl_co2 ) 
    266       IF(lwp) THEN                        ! control print 
    267          WRITE(numout,*) 
    268          WRITE(numout,*)'sbc_cpl_init : namsbc_cpl_co2 namelist ' 
    269          WRITE(numout,*)'~~~~~~~~~~~~' 
    270          WRITE(numout,*)'   received fields' 
    271          WRITE(numout,*)'       atm co2                            cn_rcv_co2         = ', cn_rcv_co2 
    272          WRITE(numout,*)'   sent fields' 
    273          WRITE(numout,*)'      oce co2 flux                        cn_snd_co2         = ', cn_snd_co2 
    274           WRITE(numout,*) 
    275       ENDIF 
    276 #endif 
    277       ! save current & stress in an array and suppress possible blank in the name 
    278       cn_snd_crt(1) = TRIM( cn_snd_crt_nature )   ;   cn_snd_crt(2) = TRIM( cn_snd_crt_refere ) 
    279       cn_snd_crt(3) = TRIM( cn_snd_crt_orient )   ;   cn_snd_crt(4) = TRIM( cn_snd_crt_grid   ) 
    280       cn_rcv_tau(1) = TRIM( cn_rcv_tau_nature )   ;   cn_rcv_tau(2) = TRIM( cn_rcv_tau_refere ) 
    281       cn_rcv_tau(3) = TRIM( cn_rcv_tau_orient )   ;   cn_rcv_tau(4) = TRIM( cn_rcv_tau_grid   ) 
    282  
    283       !                                   ! allocate zdfric arrays 
     268         WRITE(numout,*)'  received fields (mutiple ice categogies)' 
     269         WRITE(numout,*)'      10m wind module                 = ', TRIM(sn_rcv_w10m%cldes  ), ' (', TRIM(sn_rcv_w10m%clcat  ), ')' 
     270         WRITE(numout,*)'      stress module                   = ', TRIM(sn_rcv_taumod%cldes), ' (', TRIM(sn_rcv_taumod%clcat), ')' 
     271         WRITE(numout,*)'      surface stress                  = ', TRIM(sn_rcv_tau%cldes   ), ' (', TRIM(sn_rcv_tau%clcat   ), ')' 
     272         WRITE(numout,*)'                     - referential    = ', sn_rcv_tau%clvref 
     273         WRITE(numout,*)'                     - orientation    = ', sn_rcv_tau%clvor 
     274         WRITE(numout,*)'                     - mesh           = ', sn_rcv_tau%clvgrd 
     275         WRITE(numout,*)'      non-solar heat flux sensitivity = ', TRIM(sn_rcv_dqnsdt%cldes), ' (', TRIM(sn_rcv_dqnsdt%clcat), ')' 
     276         WRITE(numout,*)'      solar heat flux                 = ', TRIM(sn_rcv_qsr%cldes   ), ' (', TRIM(sn_rcv_qsr%clcat   ), ')' 
     277         WRITE(numout,*)'      non-solar heat flux             = ', TRIM(sn_rcv_qns%cldes   ), ' (', TRIM(sn_rcv_qns%clcat   ), ')' 
     278         WRITE(numout,*)'      freshwater budget               = ', TRIM(sn_rcv_emp%cldes   ), ' (', TRIM(sn_rcv_emp%clcat   ), ')' 
     279         WRITE(numout,*)'      runoffs                         = ', TRIM(sn_rcv_rnf%cldes   ), ' (', TRIM(sn_rcv_rnf%clcat   ), ')' 
     280         WRITE(numout,*)'      calving                         = ', TRIM(sn_rcv_cal%cldes   ), ' (', TRIM(sn_rcv_cal%clcat   ), ')' 
     281         WRITE(numout,*)'      sea ice heat fluxes             = ', TRIM(sn_rcv_iceflx%cldes), ' (', TRIM(sn_rcv_iceflx%clcat), ')' 
     282         WRITE(numout,*)'      atm co2                         = ', TRIM(sn_rcv_co2%cldes   ), ' (', TRIM(sn_rcv_co2%clcat   ), ')' 
     283         WRITE(numout,*)'  sent fields (multiple ice categories)' 
     284         WRITE(numout,*)'      surface temperature             = ', TRIM(sn_snd_temp%cldes  ), ' (', TRIM(sn_snd_temp%clcat  ), ')' 
     285         WRITE(numout,*)'      albedo                          = ', TRIM(sn_snd_alb%cldes   ), ' (', TRIM(sn_snd_alb%clcat   ), ')' 
     286         WRITE(numout,*)'      ice/snow thickness              = ', TRIM(sn_snd_thick%cldes ), ' (', TRIM(sn_snd_thick%clcat ), ')' 
     287         WRITE(numout,*)'      surface current                 = ', TRIM(sn_snd_crt%cldes   ), ' (', TRIM(sn_snd_crt%clcat   ), ')' 
     288         WRITE(numout,*)'                      - referential   = ', sn_snd_crt%clvref  
     289         WRITE(numout,*)'                      - orientation   = ', sn_snd_crt%clvor 
     290         WRITE(numout,*)'                      - mesh          = ', sn_snd_crt%clvgrd 
     291         WRITE(numout,*)'      oce co2 flux                    = ', TRIM(sn_snd_co2%cldes   ), ' (', TRIM(sn_snd_co2%clcat   ), ')' 
     292      ENDIF 
     293 
     294      !                                   ! allocate sbccpl arrays 
    284295      IF( sbc_cpl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' ) 
    285296      
     
    294305 
    295306      ! default definitions of srcv 
    296       srcv(:)%laction = .FALSE.   ;   srcv(:)%clgrid = 'T'   ;   srcv(:)%nsgn = 1. 
     307      srcv(:)%laction = .FALSE.   ;   srcv(:)%clgrid = 'T'   ;   srcv(:)%nsgn = 1.   ;   srcv(:)%nct = 1 
    297308 
    298309      !                                                      ! ------------------------- ! 
     
    315326      !  
    316327      ! Vectors: change of sign at north fold ONLY if on the local grid 
    317       IF( TRIM( cn_rcv_tau(3) ) == 'local grid' )   srcv(jpr_otx1:jpr_itz2)%nsgn = -1. 
     328      IF( TRIM( sn_rcv_tau%clvor ) == 'local grid' )   srcv(jpr_otx1:jpr_itz2)%nsgn = -1. 
    318329       
    319330      !                                                           ! Set grid and action 
    320       SELECT CASE( TRIM( cn_rcv_tau(4) ) )      !  'T', 'U,V', 'U,V,I', 'U,V,F', 'T,I', 'T,F', or 'T,U,V' 
     331      SELECT CASE( TRIM( sn_rcv_tau%clvgrd ) )      !  'T', 'U,V', 'U,V,I', 'U,V,F', 'T,I', 'T,F', or 'T,U,V' 
    321332      CASE( 'T' )  
    322333         srcv(jpr_otx1:jpr_itz2)%clgrid  = 'T'        ! oce and ice components given at T-point 
     
    364375         srcv(jpr_itx1:jpr_itz2)%laction = .TRUE.     ! receive ice components on grid 1 & 2 
    365376      CASE default    
    366          CALL ctl_stop( 'sbc_cpl_init: wrong definition of cn_rcv_tau(4)' ) 
     377         CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_tau%clvgrd' ) 
    367378      END SELECT 
    368379      ! 
    369       IF( TRIM( cn_rcv_tau(2) ) == 'spherical' )   &           ! spherical: 3rd component not received 
     380      IF( TRIM( sn_rcv_tau%clvref ) == 'spherical' )   &           ! spherical: 3rd component not received 
    370381         &     srcv( (/jpr_otz1, jpr_otz2, jpr_itz1, jpr_itz2/) )%laction = .FALSE.  
    371382      ! 
    372       IF( TRIM( cn_rcv_tau(1) ) /= 'oce and ice' ) THEN        ! 'oce and ice' case ocean stress on ocean mesh used 
     383      IF( TRIM( sn_rcv_tau%cldes ) /= 'oce and ice' ) THEN        ! 'oce and ice' case ocean stress on ocean mesh used 
    373384         srcv(jpr_itx1:jpr_itz2)%laction = .FALSE.    ! ice components not received 
    374385         srcv(jpr_itx1)%clgrid = 'U'                  ! ocean stress used after its transformation 
     
    388399      srcv(jpr_semp)%clname = 'OISubMSn'      ! ice solid water budget = sublimation - solid precipitation 
    389400      srcv(jpr_oemp)%clname = 'OOEvaMPr'      ! ocean water budget = ocean Evap - ocean precip 
    390       SELECT CASE( TRIM( cn_rcv_emp ) ) 
     401      SELECT CASE( TRIM( sn_rcv_emp%cldes ) ) 
    391402      CASE( 'oce only'      )   ;   srcv(                                 jpr_oemp   )%laction = .TRUE.  
    392403      CASE( 'conservative'  )   ;   srcv( (/jpr_rain, jpr_snow, jpr_ievp, jpr_tevp/) )%laction = .TRUE. 
    393404      CASE( 'oce and ice'   )   ;   srcv( (/jpr_ievp, jpr_sbpr, jpr_semp, jpr_oemp/) )%laction = .TRUE. 
    394       CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of cn_rcv_emp' ) 
     405      CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_emp%cldes' ) 
    395406      END SELECT 
    396407 
     
    398409      !                                                      !     Runoffs & Calving     !    
    399410      !                                                      ! ------------------------- ! 
    400       srcv(jpr_rnf   )%clname = 'O_Runoff'   ;   IF( TRIM( cn_rcv_rnf ) == 'coupled' )   srcv(jpr_rnf)%laction = .TRUE. 
    401                                                  IF( TRIM( cn_rcv_rnf ) == 'climato' )   THEN   ;   ln_rnf = .TRUE. 
    402                                                  ELSE                                           ;   ln_rnf = .FALSE. 
    403                                                  ENDIF 
    404       srcv(jpr_cal   )%clname = 'OCalving'   ;   IF( TRIM( cn_rcv_cal ) == 'coupled' )   srcv(jpr_cal)%laction = .TRUE. 
     411      srcv(jpr_rnf   )%clname = 'O_Runoff'   ;   IF( TRIM( sn_rcv_rnf%cldes ) == 'coupled' )   srcv(jpr_rnf)%laction = .TRUE. 
     412! This isn't right - really just want ln_rnf_emp changed 
     413!                                                 IF( TRIM( sn_rcv_rnf%cldes ) == 'climato' )   THEN   ;   ln_rnf = .TRUE. 
     414!                                                 ELSE                                                 ;   ln_rnf = .FALSE. 
     415!                                                 ENDIF 
     416      srcv(jpr_cal   )%clname = 'OCalving'   ;   IF( TRIM( sn_rcv_cal%cldes ) == 'coupled' )   srcv(jpr_cal)%laction = .TRUE. 
    405417 
    406418      !                                                      ! ------------------------- ! 
     
    410422      srcv(jpr_qnsice)%clname = 'O_QnsIce' 
    411423      srcv(jpr_qnsmix)%clname = 'O_QnsMix' 
    412       SELECT CASE( TRIM( cn_rcv_qns ) ) 
     424      SELECT CASE( TRIM( sn_rcv_qns%cldes ) ) 
    413425      CASE( 'oce only'      )   ;   srcv(               jpr_qnsoce   )%laction = .TRUE. 
    414426      CASE( 'conservative'  )   ;   srcv( (/jpr_qnsice, jpr_qnsmix/) )%laction = .TRUE. 
    415427      CASE( 'oce and ice'   )   ;   srcv( (/jpr_qnsice, jpr_qnsoce/) )%laction = .TRUE. 
    416428      CASE( 'mixed oce-ice' )   ;   srcv(               jpr_qnsmix   )%laction = .TRUE.  
    417       CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of cn_rcv_qns' ) 
     429      CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_qns%cldes' ) 
    418430      END SELECT 
    419  
     431      IF( TRIM( sn_rcv_qns%cldes ) == 'mixed oce-ice' .AND. jpl > 1 ) & 
     432         CALL ctl_stop( 'sbc_cpl_init: sn_rcv_qns%cldes not currently allowed to be mixed oce-ice for multi-category ice' ) 
    420433      !                                                      ! ------------------------- ! 
    421434      !                                                      !    solar radiation        !   Qsr 
     
    424437      srcv(jpr_qsrice)%clname = 'O_QsrIce' 
    425438      srcv(jpr_qsrmix)%clname = 'O_QsrMix' 
    426       SELECT CASE( TRIM( cn_rcv_qsr ) ) 
     439      SELECT CASE( TRIM( sn_rcv_qsr%cldes ) ) 
    427440      CASE( 'oce only'      )   ;   srcv(               jpr_qsroce   )%laction = .TRUE. 
    428441      CASE( 'conservative'  )   ;   srcv( (/jpr_qsrice, jpr_qsrmix/) )%laction = .TRUE. 
    429442      CASE( 'oce and ice'   )   ;   srcv( (/jpr_qsrice, jpr_qsroce/) )%laction = .TRUE. 
    430443      CASE( 'mixed oce-ice' )   ;   srcv(               jpr_qsrmix   )%laction = .TRUE.  
    431       CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of cn_rcv_qsr' ) 
     444      CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_qsr%cldes' ) 
    432445      END SELECT 
    433  
     446      IF( TRIM( sn_rcv_qsr%cldes ) == 'mixed oce-ice' .AND. jpl > 1 ) & 
     447         CALL ctl_stop( 'sbc_cpl_init: sn_rcv_qsr%cldes not currently allowed to be mixed oce-ice for multi-category ice' ) 
    434448      !                                                      ! ------------------------- ! 
    435449      !                                                      !   non solar sensitivity   !   d(Qns)/d(T) 
    436450      !                                                      ! ------------------------- ! 
    437451      srcv(jpr_dqnsdt)%clname = 'O_dQnsdT'    
    438       IF( TRIM( cn_rcv_dqnsdt ) == 'coupled' )   srcv(jpr_dqnsdt)%laction = .TRUE. 
    439       ! 
    440       ! non solar sensitivity mandatory for ice model 
    441       IF( TRIM( cn_rcv_dqnsdt ) == 'none' .AND. k_ice /= 0 ) & 
    442          CALL ctl_stop( 'sbc_cpl_init: cn_rcv_dqnsdt must be coupled in namsbc_cpl namelist' ) 
     452      IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'coupled' )   srcv(jpr_dqnsdt)%laction = .TRUE. 
     453      ! 
     454      ! non solar sensitivity mandatory for LIM ice model 
     455      IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'none' .AND. k_ice /= 0 .AND. k_ice /= 4) & 
     456         CALL ctl_stop( 'sbc_cpl_init: sn_rcv_dqnsdt%cldes must be coupled in namsbc_cpl namelist' ) 
    443457      ! non solar sensitivity mandatory for mixed oce-ice solar radiation coupling technique 
    444       IF( TRIM( cn_rcv_dqnsdt ) == 'none' .AND. TRIM( cn_rcv_qns ) == 'mixed oce-ice' ) & 
    445          CALL ctl_stop( 'sbc_cpl_init: namsbc_cpl namelist mismatch between cn_rcv_qns and cn_rcv_dqnsdt' ) 
     458      IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'none' .AND. TRIM( sn_rcv_qns%cldes ) == 'mixed oce-ice' ) & 
     459         CALL ctl_stop( 'sbc_cpl_init: namsbc_cpl namelist mismatch between sn_rcv_qns%cldes and sn_rcv_dqnsdt%cldes' ) 
    446460      !                                                      ! ------------------------- ! 
    447461      !                                                      !    Ice Qsr penetration    !    
     
    456470      !                                                      !      10m wind module      !    
    457471      !                                                      ! ------------------------- ! 
    458       srcv(jpr_w10m)%clname = 'O_Wind10'   ;   IF( TRIM(cn_rcv_w10m  ) == 'coupled' )   srcv(jpr_w10m)%laction = .TRUE.  
     472      srcv(jpr_w10m)%clname = 'O_Wind10'   ;   IF( TRIM(sn_rcv_w10m%cldes  ) == 'coupled' )   srcv(jpr_w10m)%laction = .TRUE.  
    459473      ! 
    460474      !                                                      ! ------------------------- ! 
    461475      !                                                      !   wind stress module      !    
    462476      !                                                      ! ------------------------- ! 
    463       srcv(jpr_taum)%clname = 'O_TauMod'   ;   IF( TRIM(cn_rcv_taumod) == 'coupled' )   srcv(jpr_taum)%laction = .TRUE. 
     477      srcv(jpr_taum)%clname = 'O_TauMod'   ;   IF( TRIM(sn_rcv_taumod%cldes) == 'coupled' )   srcv(jpr_taum)%laction = .TRUE. 
    464478      lhftau = srcv(jpr_taum)%laction 
    465479 
    466 #if defined key_cpl_carbon_cycle 
    467480      !                                                      ! ------------------------- ! 
    468481      !                                                      !      Atmospheric CO2      ! 
    469482      !                                                      ! ------------------------- ! 
    470       srcv(jpr_co2 )%clname = 'O_AtmCO2'   ;   IF( TRIM(cn_rcv_co2   ) == 'coupled' )    srcv(jpr_co2 )%laction = .TRUE. 
    471 #endif 
    472       
     483      srcv(jpr_co2 )%clname = 'O_AtmCO2'   ;   IF( TRIM(sn_rcv_co2%cldes   ) == 'coupled' )    srcv(jpr_co2 )%laction = .TRUE. 
     484      !                                                      ! ------------------------- ! 
     485      !                                                      !   topmelt and botmelt     !    
     486      !                                                      ! ------------------------- ! 
     487      srcv(jpr_topm )%clname = 'OTopMlt' 
     488      srcv(jpr_botm )%clname = 'OBotMlt' 
     489      IF( TRIM(sn_rcv_iceflx%cldes) == 'coupled' ) THEN 
     490         IF ( TRIM( sn_rcv_iceflx%clcat ) == 'yes' ) THEN 
     491            srcv(jpr_topm:jpr_botm)%nct = jpl 
     492         ELSE 
     493            CALL ctl_stop( 'sbc_cpl_init: sn_rcv_iceflx%clcat should always be set to yes currently' ) 
     494         ENDIF 
     495         srcv(jpr_topm:jpr_botm)%laction = .TRUE. 
     496      ENDIF 
     497 
     498      ! Allocate all parts of frcv used for received fields 
     499      DO jn = 1, jprcv 
     500         IF ( srcv(jn)%laction ) ALLOCATE( frcv(jn)%z3(jpi,jpj,srcv(jn)%nct) ) 
     501      END DO 
     502      ! Allocate taum part of frcv which is used even when not received as coupling field 
     503      IF ( .NOT. srcv(jpr_taum)%laction ) ALLOCATE( frcv(jpr_taum)%z3(jpi,jpj,srcv(jn)%nct) ) 
     504 
    473505      ! ================================ ! 
    474506      !     Define the send interface    ! 
    475507      ! ================================ ! 
    476       ! for each field: define the OASIS name                           (srcv(:)%clname) 
    477       !                 define send or not from the namelist parameters (srcv(:)%laction) 
    478       !                 define the north fold type of lbc               (srcv(:)%nsgn) 
     508      ! for each field: define the OASIS name                           (ssnd(:)%clname) 
     509      !                 define send or not from the namelist parameters (ssnd(:)%laction) 
     510      !                 define the north fold type of lbc               (ssnd(:)%nsgn) 
    479511       
    480512      ! default definitions of nsnd 
    481       ssnd(:)%laction = .FALSE.   ;   ssnd(:)%clgrid = 'T'   ;   ssnd(:)%nsgn = 1. 
     513      ssnd(:)%laction = .FALSE.   ;   ssnd(:)%clgrid = 'T'   ;   ssnd(:)%nsgn = 1.  ; ssnd(:)%nct = 1 
    482514          
    483515      !                                                      ! ------------------------- ! 
     
    487519      ssnd(jps_tice)%clname = 'O_TepIce' 
    488520      ssnd(jps_tmix)%clname = 'O_TepMix' 
    489       SELECT CASE( TRIM( cn_snd_temperature ) ) 
     521      SELECT CASE( TRIM( sn_snd_temp%cldes ) ) 
    490522      CASE( 'oce only'             )   ;   ssnd(   jps_toce             )%laction = .TRUE. 
    491       CASE( 'weighted oce and ice' )   ;   ssnd( (/jps_toce, jps_tice/) )%laction = .TRUE. 
     523      CASE( 'weighted oce and ice' ) 
     524         ssnd( (/jps_toce, jps_tice/) )%laction = .TRUE. 
     525         IF ( TRIM( sn_snd_temp%clcat ) == 'yes' )  ssnd(jps_tice)%nct = jpl 
    492526      CASE( 'mixed oce-ice'        )   ;   ssnd(   jps_tmix             )%laction = .TRUE. 
    493       CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of cn_snd_temperature' ) 
     527      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_temp%cldes' ) 
    494528      END SELECT 
    495529      
     
    499533      ssnd(jps_albice)%clname = 'O_AlbIce'  
    500534      ssnd(jps_albmix)%clname = 'O_AlbMix' 
    501       SELECT CASE( TRIM( cn_snd_albedo ) ) 
     535      SELECT CASE( TRIM( sn_snd_alb%cldes ) ) 
    502536      CASE( 'none'          )       ! nothing to do 
    503537      CASE( 'weighted ice'  )   ;   ssnd(jps_albice)%laction = .TRUE. 
    504538      CASE( 'mixed oce-ice' )   ;   ssnd(jps_albmix)%laction = .TRUE. 
    505       CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of cn_snd_albedo' ) 
     539      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_alb%cldes' ) 
    506540      END SELECT 
    507541      ! 
     
    509543      !     1. sending mixed oce-ice albedo or 
    510544      !     2. receiving mixed oce-ice solar radiation  
    511       IF ( TRIM ( cn_snd_albedo ) == 'mixed oce-ice' .OR. TRIM ( cn_rcv_qsr ) == 'mixed oce-ice' ) THEN 
     545      IF ( TRIM ( sn_snd_alb%cldes ) == 'mixed oce-ice' .OR. TRIM ( sn_rcv_qsr%cldes ) == 'mixed oce-ice' ) THEN 
    512546         CALL albedo_oce( zaos, zacs ) 
    513547         ! Due to lack of information on nebulosity : mean clear/overcast sky 
     
    518552      !                                                      !  Ice fraction & Thickness !  
    519553      !                                                      ! ------------------------- ! 
    520       ssnd(jps_fice)%clname = 'OIceFrac'    
    521       ssnd(jps_hice)%clname = 'O_IceTck' 
    522       ssnd(jps_hsnw)%clname = 'O_SnwTck' 
    523       IF( k_ice /= 0 )   ssnd(jps_fice)%laction = .TRUE.       ! if ice treated in the ocean (even in climato case) 
    524       IF( TRIM( cn_snd_thickness ) == 'weighted ice and snow' )   ssnd( (/jps_hice, jps_hsnw/) )%laction = .TRUE. 
    525           
     554      ssnd(jps_fice)%clname = 'OIceFrc' 
     555      ssnd(jps_hice)%clname = 'OIceTck' 
     556      ssnd(jps_hsnw)%clname = 'OSnwTck' 
     557      IF( k_ice /= 0 ) THEN 
     558         ssnd(jps_fice)%laction = .TRUE.                  ! if ice treated in the ocean (even in climato case) 
     559! Currently no namelist entry to determine sending of multi-category ice fraction so use the thickness entry for now 
     560         IF ( TRIM( sn_snd_thick%clcat ) == 'yes' ) ssnd(jps_fice)%nct = jpl 
     561      ENDIF 
     562 
     563      SELECT CASE ( TRIM( sn_snd_thick%cldes ) ) 
     564      CASE ( 'ice and snow' )  
     565         ssnd(jps_hice:jps_hsnw)%laction = .TRUE. 
     566         IF ( TRIM( sn_snd_thick%clcat ) == 'yes' ) THEN 
     567            ssnd(jps_hice:jps_hsnw)%nct = jpl 
     568         ELSE 
     569            IF ( jpl > 1 ) THEN 
     570               CALL ctl_stop( 'sbc_cpl_init: use weighted ice and snow option for sn_snd_thick%cldes if not exchanging category fields' ) 
     571            ENDIF 
     572         ENDIF 
     573      CASE ( 'weighted ice and snow' )  
     574         ssnd(jps_hice:jps_hsnw)%laction = .TRUE. 
     575         IF ( TRIM( sn_snd_thick%clcat ) == 'yes' ) ssnd(jps_hice:jps_hsnw)%nct = jpl 
     576      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_thick%cldes' ) 
     577      END SELECT 
     578 
    526579      !                                                      ! ------------------------- ! 
    527580      !                                                      !      Surface current      ! 
     
    534587      ssnd(jps_ocx1:jps_ivz1)%nsgn = -1.   ! vectors: change of the sign at the north fold 
    535588 
    536       IF( cn_snd_crt(4) /= 'T' )   CALL ctl_stop( 'cn_snd_crt(4) must be equal to T' ) 
    537       ssnd(jps_ocx1:jps_ivz1)%clgrid  = 'T'      ! all oce and ice components on the same unique grid 
    538  
     589      IF( sn_snd_crt%clvgrd == 'U,V' ) THEN 
     590         ssnd(jps_ocx1)%clgrid = 'U' ; ssnd(jps_ocy1)%clgrid = 'V' 
     591      ELSE IF( sn_snd_crt%clvgrd /= 'T' ) THEN   
     592         CALL ctl_stop( 'sn_snd_crt%clvgrd must be equal to T' ) 
     593         ssnd(jps_ocx1:jps_ivz1)%clgrid  = 'T'      ! all oce and ice components on the same unique grid 
     594      ENDIF 
    539595      ssnd(jps_ocx1:jps_ivz1)%laction = .TRUE.   ! default: all are send 
    540       IF( TRIM( cn_snd_crt(2) ) == 'spherical' )   ssnd( (/jps_ocz1, jps_ivz1/) )%laction = .FALSE.  
    541       SELECT CASE( TRIM( cn_snd_crt(1) ) ) 
     596      IF( TRIM( sn_snd_crt%clvref ) == 'spherical' )   ssnd( (/jps_ocz1, jps_ivz1/) )%laction = .FALSE.  
     597      IF( TRIM( sn_snd_crt%clvor ) == 'eastward-northward' ) ssnd(jps_ocx1:jps_ivz1)%nsgn = 1. 
     598      SELECT CASE( TRIM( sn_snd_crt%cldes ) ) 
    542599      CASE( 'none'                 )   ;   ssnd(jps_ocx1:jps_ivz1)%laction = .FALSE. 
    543600      CASE( 'oce only'             )   ;   ssnd(jps_ivx1:jps_ivz1)%laction = .FALSE. 
    544601      CASE( 'weighted oce and ice' )   !   nothing to do 
    545602      CASE( 'mixed oce-ice'        )   ;   ssnd(jps_ivx1:jps_ivz1)%laction = .FALSE. 
    546       CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of cn_snd_crt(1)' ) 
     603      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_crt%cldes' ) 
    547604      END SELECT 
    548605 
    549 #if defined key_cpl_carbon_cycle 
    550606      !                                                      ! ------------------------- ! 
    551607      !                                                      !          CO2 flux         ! 
    552608      !                                                      ! ------------------------- ! 
    553       ssnd(jps_co2)%clname = 'O_CO2FLX' ;  IF( TRIM(cn_snd_co2) == 'coupled' )    ssnd(jps_co2 )%laction = .TRUE. 
    554 #endif 
     609      ssnd(jps_co2)%clname = 'O_CO2FLX' ;  IF( TRIM(sn_snd_co2%cldes) == 'coupled' )    ssnd(jps_co2 )%laction = .TRUE. 
    555610      ! 
    556611      ! ================================ ! 
     
    636691      isec = ( kt - nit000 ) * NINT( rdttra(1) )             ! date of exchanges 
    637692      DO jn = 1, jprcv                                       ! received fields sent by the atmosphere 
    638          IF( srcv(jn)%laction )   CALL cpl_prism_rcv( jn, isec, frcv(:,:,jn), nrcvinfo(jn) ) 
     693         IF( srcv(jn)%laction )   CALL cpl_prism_rcv( jn, isec, frcv(jn)%z3, nrcvinfo(jn) ) 
    639694      END DO 
    640695 
     
    642697      IF( srcv(jpr_otx1)%laction ) THEN                      !  ocean stress components  ! 
    643698         !                                                   ! ========================= ! 
    644          ! define frcv(:,:,jpr_otx1) and frcv(:,:,jpr_oty1): stress at U/V point along model grid 
     699         ! define frcv(jpr_otx1)%z3(:,:,1) and frcv(jpr_oty1)%z3(:,:,1): stress at U/V point along model grid 
    645700         ! => need to be done only when we receive the field 
    646701         IF(  nrcvinfo(jpr_otx1) == OASIS_Rcv ) THEN 
    647702            ! 
    648             IF( TRIM( cn_rcv_tau(2) ) == 'cartesian' ) THEN            ! 2 components on the sphere 
     703            IF( TRIM( sn_rcv_tau%clvref ) == 'cartesian' ) THEN            ! 2 components on the sphere 
    649704               !                                                       ! (cartesian to spherical -> 3 to 2 components) 
    650705               ! 
    651                CALL geo2oce( frcv(:,:,jpr_otx1), frcv(:,:,jpr_oty1), frcv(:,:,jpr_otz1),   & 
     706               CALL geo2oce( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), frcv(jpr_otz1)%z3(:,:,1),   & 
    652707                  &          srcv(jpr_otx1)%clgrid, ztx, zty ) 
    653                frcv(:,:,jpr_otx1) = ztx(:,:)   ! overwrite 1st comp. on the 1st grid 
    654                frcv(:,:,jpr_oty1) = zty(:,:)   ! overwrite 2nd comp. on the 1st grid 
     708               frcv(jpr_otx1)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 1st grid 
     709               frcv(jpr_oty1)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 1st grid 
    655710               ! 
    656711               IF( srcv(jpr_otx2)%laction ) THEN 
    657                   CALL geo2oce( frcv(:,:,jpr_otx2), frcv(:,:,jpr_oty2), frcv(:,:,jpr_otz2),   & 
     712                  CALL geo2oce( frcv(jpr_otx2)%z3(:,:,1), frcv(jpr_oty2)%z3(:,:,1), frcv(jpr_otz2)%z3(:,:,1),   & 
    658713                     &          srcv(jpr_otx2)%clgrid, ztx, zty ) 
    659                   frcv(:,:,jpr_otx2) = ztx(:,:)   ! overwrite 1st comp. on the 2nd grid 
    660                   frcv(:,:,jpr_oty2) = zty(:,:)   ! overwrite 2nd comp. on the 2nd grid 
     714                  frcv(jpr_otx2)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 2nd grid 
     715                  frcv(jpr_oty2)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 2nd grid 
    661716               ENDIF 
    662717               ! 
    663718            ENDIF 
    664719            ! 
    665             IF( TRIM( cn_rcv_tau(3) ) == 'eastward-northward' ) THEN   ! 2 components oriented along the local grid 
     720            IF( TRIM( sn_rcv_tau%clvor ) == 'eastward-northward' ) THEN   ! 2 components oriented along the local grid 
    666721               !                                                       ! (geographical to local grid -> rotate the components) 
    667                CALL rot_rep( frcv(:,:,jpr_otx1), frcv(:,:,jpr_oty1), srcv(jpr_otx1)%clgrid, 'en->i', ztx )    
    668                frcv(:,:,jpr_otx1) = ztx(:,:)      ! overwrite 1st component on the 1st grid 
     722               CALL rot_rep( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), srcv(jpr_otx1)%clgrid, 'en->i', ztx )    
     723               frcv(jpr_otx1)%z3(:,:,1) = ztx(:,:)      ! overwrite 1st component on the 1st grid 
    669724               IF( srcv(jpr_otx2)%laction ) THEN 
    670                   CALL rot_rep( frcv(:,:,jpr_otx2), frcv(:,:,jpr_oty2), srcv(jpr_otx2)%clgrid, 'en->j', zty )    
    671                ELSE 
    672                   CALL rot_rep( frcv(:,:,jpr_otx1), frcv(:,:,jpr_oty1), srcv(jpr_otx1)%clgrid, 'en->j', zty )   
     725                  CALL rot_rep( frcv(jpr_otx2)%z3(:,:,1), frcv(jpr_oty2)%z3(:,:,1), srcv(jpr_otx2)%clgrid, 'en->j', zty )    
     726               ELSE   
     727                  CALL rot_rep( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), srcv(jpr_otx1)%clgrid, 'en->j', zty )   
    673728               ENDIF 
    674                frcv(:,:,jpr_oty1) = zty(:,:)      ! overwrite 2nd component on the 2nd grid 
     729               frcv(jpr_oty1)%z3(:,:,1) = zty(:,:)      ! overwrite 2nd component on the 2nd grid 
    675730            ENDIF 
    676731            !                               
     
    678733               DO jj = 2, jpjm1                                          ! T ==> (U,V) 
    679734                  DO ji = fs_2, fs_jpim1   ! vector opt. 
    680                      frcv(ji,jj,jpr_otx1) = 0.5 * ( frcv(ji+1,jj  ,jpr_otx1) + frcv(ji,jj,jpr_otx1) ) 
    681                      frcv(ji,jj,jpr_oty1) = 0.5 * ( frcv(ji  ,jj+1,jpr_oty1) + frcv(ji,jj,jpr_oty1) ) 
     735                     frcv(jpr_otx1)%z3(ji,jj,1) = 0.5 * ( frcv(jpr_otx1)%z3(ji+1,jj  ,1) + frcv(jpr_otx1)%z3(ji,jj,1) ) 
     736                     frcv(jpr_oty1)%z3(ji,jj,1) = 0.5 * ( frcv(jpr_oty1)%z3(ji  ,jj+1,1) + frcv(jpr_oty1)%z3(ji,jj,1) ) 
    682737                  END DO 
    683738               END DO 
    684                CALL lbc_lnk( frcv(:,:,jpr_otx1), 'U',  -1. )   ;   CALL lbc_lnk( frcv(:,:,jpr_oty1), 'V',  -1. ) 
     739               CALL lbc_lnk( frcv(jpr_otx1)%z3(:,:,1), 'U',  -1. )   ;   CALL lbc_lnk( frcv(jpr_oty1)%z3(:,:,1), 'V',  -1. ) 
    685740            ENDIF 
    686741            llnewtx = .TRUE. 
     
    691746      ELSE                                                   !   No dynamical coupling   ! 
    692747         !                                                   ! ========================= ! 
    693          frcv(:,:,jpr_otx1) = 0.e0                               ! here simply set to zero  
    694          frcv(:,:,jpr_oty1) = 0.e0                               ! an external read in a file can be added instead 
     748         frcv(jpr_otx1)%z3(:,:,1) = 0.e0                               ! here simply set to zero  
     749         frcv(jpr_oty1)%z3(:,:,1) = 0.e0                               ! an external read in a file can be added instead 
    695750         llnewtx = .TRUE. 
    696751         ! 
     
    708763!CDIR NOVERRCHK 
    709764               DO ji = fs_2, fs_jpim1   ! vect. opt. 
    710                   zzx = frcv(ji-1,jj  ,jpr_otx1) + frcv(ji,jj,jpr_otx1)  
    711                   zzy = frcv(ji  ,jj-1,jpr_oty1) + frcv(ji,jj,jpr_oty1)  
    712                   frcv(ji,jj,jpr_taum) = 0.5 * SQRT( zzx * zzx + zzy * zzy ) 
     765                  zzx = frcv(jpr_otx1)%z3(ji-1,jj  ,1) + frcv(jpr_otx1)%z3(ji,jj,1) 
     766                  zzy = frcv(jpr_oty1)%z3(ji  ,jj-1,1) + frcv(jpr_oty1)%z3(ji,jj,1) 
     767                  frcv(jpr_taum)%z3(ji,jj,1) = 0.5 * SQRT( zzx * zzx + zzy * zzy ) 
    713768               END DO 
    714769            END DO 
    715             CALL lbc_lnk( frcv(:,:,jpr_taum), 'T', 1. ) 
     770            CALL lbc_lnk( frcv(jpr_taum)%z3(:,:,1), 'T', 1. ) 
    716771            llnewtau = .TRUE. 
    717772         ELSE 
     
    722777         ! Stress module can be negative when received (interpolation problem) 
    723778         IF( llnewtau ) THEN  
    724             DO jj = 1, jpj 
    725                DO ji = 1, jpi  
    726                   frcv(ji,jj,jpr_taum) = MAX( 0.0e0, frcv(ji,jj,jpr_taum) ) 
    727                END DO 
    728             END DO 
     779            frcv(jpr_taum)%z3(:,:,1) = MAX( 0.0e0, frcv(jpr_taum)%z3(:,:,1) ) 
    729780         ENDIF 
    730781      ENDIF 
     
    742793!CDIR NOVERRCHK 
    743794               DO ji = 1, jpi  
    744                   frcv(ji,jj,jpr_w10m) = SQRT( frcv(ji,jj,jpr_taum) * zcoef ) 
     795                  wndm(ji,jj) = SQRT( frcv(jpr_taum)%z3(ji,jj,1) * zcoef ) 
    745796               END DO 
    746797            END DO 
    747798         ENDIF 
    748       ENDIF 
    749  
    750       ! u(v)tau and taum will be modified by ice model (wndm will be changed by PISCES) 
     799      ELSE 
     800         IF ( nrcvinfo(jpr_w10m) == OASIS_Rcv ) wndm(:,:) = frcv(jpr_w10m)%z3(:,:,1) 
     801      ENDIF 
     802 
     803      ! u(v)tau and taum will be modified by ice model 
    751804      ! -> need to be reset before each call of the ice/fsbc       
    752805      IF( MOD( kt-1, k_fsbc ) == 0 ) THEN 
    753806         ! 
    754          utau(:,:) = frcv(:,:,jpr_otx1)                    
    755          vtau(:,:) = frcv(:,:,jpr_oty1) 
    756          taum(:,:) = frcv(:,:,jpr_taum) 
    757          wndm(:,:) = frcv(:,:,jpr_w10m) 
     807         utau(:,:) = frcv(jpr_otx1)%z3(:,:,1) 
     808         vtau(:,:) = frcv(jpr_oty1)%z3(:,:,1) 
     809         taum(:,:) = frcv(jpr_taum)%z3(:,:,1) 
    758810         CALL iom_put( "taum_oce", taum )   ! output wind stress module 
    759811         !   
    760812      ENDIF 
     813 
     814#if defined key_cpl_carbon_cycle 
     815      !                                                              ! atmosph. CO2 (ppm) 
     816      IF( srcv(jpr_co2)%laction )   atm_co2(:,:) = frcv(jpr_co2)%z3(:,:,1) 
     817#endif 
     818 
    761819      !                                                      ! ========================= ! 
    762820      IF( k_ice <= 1 ) THEN                                  !  heat & freshwater fluxes ! (Ocean only case) 
     
    764822         ! 
    765823         !                                                       ! non solar heat flux over the ocean (qns) 
    766          IF( srcv(jpr_qnsoce)%laction )   qns(:,:) = frcv(:,:,jpr_qnsoce) 
    767          IF( srcv(jpr_qnsmix)%laction )   qns(:,:) = frcv(:,:,jpr_qnsmix)   
     824         IF( srcv(jpr_qnsoce)%laction )   qns(:,:) = frcv(jpr_qnsoce)%z3(:,:,1) 
     825         IF( srcv(jpr_qnsmix)%laction )   qns(:,:) = frcv(jpr_qnsmix)%z3(:,:,1) 
    768826         ! add the latent heat of solid precip. melting 
    769          IF( srcv(jpr_snow  )%laction )   qns(:,:) = qns(:,:) - frcv(:,:,jpr_snow) * lfus               
     827         IF( srcv(jpr_snow  )%laction )   qns(:,:) = qns(:,:) - frcv(jpr_snow)%z3(:,:,1) * lfus               
    770828 
    771829         !                                                       ! solar flux over the ocean          (qsr) 
    772          IF( srcv(jpr_qsroce)%laction )   qsr(:,:) = frcv(:,:,jpr_qsroce)  
    773          IF( srcv(jpr_qsrmix)%laction )   qsr(:,:) = frcv(:,:,jpr_qsrmix) 
     830         IF( srcv(jpr_qsroce)%laction )   qsr(:,:) = frcv(jpr_qsroce)%z3(:,:,1) 
     831         IF( srcv(jpr_qsrmix)%laction )   qsr(:,:) = frcv(jpr_qsrmix)%z3(:,:,1) 
    774832         IF( ln_dm2dc )   qsr(:,:) = sbc_dcy( qsr )                           ! modify qsr to include the diurnal cycle 
    775833         ! 
    776834         !                                                       ! total freshwater fluxes over the ocean (emp, emps) 
    777          SELECT CASE( TRIM( cn_rcv_emp ) )                                    ! evaporation - precipitation 
     835         SELECT CASE( TRIM( sn_rcv_emp%cldes ) )                                    ! evaporation - precipitation 
    778836         CASE( 'conservative' ) 
    779             emp(:,:) = frcv(:,:,jpr_tevp) - ( frcv(:,:,jpr_rain) + frcv(:,:,jpr_snow) ) 
     837            emp(:,:) = frcv(jpr_tevp)%z3(:,:,1) - ( frcv(jpr_rain)%z3(:,:,1) + frcv(jpr_snow)%z3(:,:,1) ) 
    780838         CASE( 'oce only', 'oce and ice' ) 
    781             emp(:,:) = frcv(:,:,jpr_oemp) 
     839            emp(:,:) = frcv(jpr_oemp)%z3(:,:,1) 
    782840         CASE default 
    783             CALL ctl_stop( 'sbc_cpl_rcv: wrong definition of cn_rcv_emp' ) 
     841            CALL ctl_stop( 'sbc_cpl_rcv: wrong definition of sn_rcv_emp%cldes' ) 
    784842         END SELECT 
    785843         ! 
    786844         !                                                        ! runoffs and calving (added in emp) 
    787          IF( srcv(jpr_rnf)%laction )   emp(:,:) = emp(:,:) - frcv(:,:,jpr_rnf)         
    788          IF( srcv(jpr_cal)%laction )   emp(:,:) = emp(:,:) - frcv(:,:,jpr_cal) 
     845         IF( srcv(jpr_rnf)%laction )   emp(:,:) = emp(:,:) - frcv(jpr_rnf)%z3(:,:,1) 
     846         IF( srcv(jpr_cal)%laction )   emp(:,:) = emp(:,:) - frcv(jpr_cal)%z3(:,:,1) 
    789847         ! 
    790848!!gm :  this seems to be internal cooking, not sure to need that in a generic interface  
    791849!!gm                                       at least should be optional... 
    792 !!         IF( TRIM( cn_rcv_rnf ) == 'coupled' ) THEN     ! add to the total freshwater budget 
     850!!         IF( TRIM( sn_rcv_rnf%cldes ) == 'coupled' ) THEN     ! add to the total freshwater budget 
    793851!!            ! remove negative runoff 
    794 !!            zcumulpos = SUM( MAX( frcv(:,:,jpr_rnf), 0.e0 ) * e1t(:,:) * e2t(:,:) * tmask_i(:,:) )  
    795 !!            zcumulneg = SUM( MIN( frcv(:,:,jpr_rnf), 0.e0 ) * e1t(:,:) * e2t(:,:) * tmask_i(:,:) ) 
     852!!            zcumulpos = SUM( MAX( frcv(jpr_rnf)%z3(:,:,1), 0.e0 ) * e1t(:,:) * e2t(:,:) * tmask_i(:,:) )  
     853!!            zcumulneg = SUM( MIN( frcv(jpr_rnf)%z3(:,:,1), 0.e0 ) * e1t(:,:) * e2t(:,:) * tmask_i(:,:) ) 
    796854!!            IF( lk_mpp )   CALL mpp_sum( zcumulpos )   ! sum over the global domain 
    797855!!            IF( lk_mpp )   CALL mpp_sum( zcumulneg )  
    798856!!            IF( zcumulpos /= 0. ) THEN                 ! distribute negative runoff on positive runoff grid points 
    799857!!               zcumulneg = 1.e0 + zcumulneg / zcumulpos 
    800 !!               frcv(:,:,jpr_rnf) = MAX( frcv(:,:,jpr_rnf), 0.e0 ) * zcumulneg 
     858!!               frcv(jpr_rnf)%z3(:,:,1) = MAX( frcv(jpr_rnf)%z3(:,:,1), 0.e0 ) * zcumulneg 
    801859!!            ENDIF      
    802860!!            ! add runoff to e-p  
    803 !!            emp(:,:) = emp(:,:) - frcv(:,:,jpr_rnf) 
     861!!            emp(:,:) = emp(:,:) - frcv(jpr_rnf)%z3(:,:,1) 
    804862!!         ENDIF 
    805863!!gm  end of internal cooking 
     
    807865         emps(:,:) = emp(:,:)                                        ! concentration/dilution = emp 
    808866   
    809          !                                                           ! 10 m wind speed 
    810          IF( srcv(jpr_w10m)%laction )   wndm(:,:) = frcv(:,:,jpr_w10m) 
    811          ! 
    812 #if defined  key_cpl_carbon_cycle 
    813          !                                                              ! atmosph. CO2 (ppm) 
    814          IF( srcv(jpr_co2)%laction )   atm_co2(:,:) = frcv(:,:,jpr_co2) 
    815 #endif 
    816  
    817867      ENDIF 
    818868      ! 
     
    880930            !                                                   ! ======================= ! 
    881931            !   
    882             IF( TRIM( cn_rcv_tau(2) ) == 'cartesian' ) THEN            ! 2 components on the sphere 
     932            IF( TRIM( sn_rcv_tau%clvref ) == 'cartesian' ) THEN            ! 2 components on the sphere 
    883933               !                                                       ! (cartesian to spherical -> 3 to 2 components) 
    884                CALL geo2oce( frcv(:,:,jpr_itx1), frcv(:,:,jpr_ity1), frcv(:,:,jpr_itz1),   & 
     934               CALL geo2oce(  frcv(jpr_itx1)%z3(:,:,1), frcv(jpr_ity1)%z3(:,:,1), frcv(jpr_itz1)%z3(:,:,1),   & 
    885935                  &          srcv(jpr_itx1)%clgrid, ztx, zty ) 
    886                frcv(:,:,jpr_itx1) = ztx(:,:)   ! overwrite 1st comp. on the 1st grid 
    887                frcv(:,:,jpr_itx1) = zty(:,:)   ! overwrite 2nd comp. on the 1st grid 
     936               frcv(jpr_itx1)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 1st grid 
     937               frcv(jpr_ity1)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 1st grid 
    888938               ! 
    889939               IF( srcv(jpr_itx2)%laction ) THEN 
    890                   CALL geo2oce( frcv(:,:,jpr_itx2), frcv(:,:,jpr_ity2), frcv(:,:,jpr_itz2),   & 
     940                  CALL geo2oce( frcv(jpr_itx2)%z3(:,:,1), frcv(jpr_ity2)%z3(:,:,1), frcv(jpr_itz2)%z3(:,:,1),   & 
    891941                     &          srcv(jpr_itx2)%clgrid, ztx, zty ) 
    892                   frcv(:,:,jpr_itx2) = ztx(:,:)   ! overwrite 1st comp. on the 2nd grid 
    893                   frcv(:,:,jpr_ity2) = zty(:,:)   ! overwrite 2nd comp. on the 2nd grid 
     942                  frcv(jpr_itx2)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 2nd grid 
     943                  frcv(jpr_ity2)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 2nd grid 
    894944               ENDIF 
    895945               ! 
    896946            ENDIF 
    897947            ! 
    898             IF( TRIM( cn_rcv_tau(3) ) == 'eastward-northward' ) THEN   ! 2 components oriented along the local grid 
     948            IF( TRIM( sn_rcv_tau%clvor ) == 'eastward-northward' ) THEN   ! 2 components oriented along the local grid 
    899949               !                                                       ! (geographical to local grid -> rotate the components) 
    900                CALL rot_rep( frcv(:,:,jpr_itx1), frcv(:,:,jpr_ity1), srcv(jpr_itx1)%clgrid, 'en->i', ztx )    
    901                frcv(:,:,jpr_itx1) = ztx(:,:)      ! overwrite 1st component on the 1st grid 
     950               CALL rot_rep( frcv(jpr_itx1)%z3(:,:,1), frcv(jpr_ity1)%z3(:,:,1), srcv(jpr_itx1)%clgrid, 'en->i', ztx )    
     951               frcv(jpr_itx1)%z3(:,:,1) = ztx(:,:)      ! overwrite 1st component on the 1st grid 
    902952               IF( srcv(jpr_itx2)%laction ) THEN 
    903                   CALL rot_rep( frcv(:,:,jpr_itx2), frcv(:,:,jpr_ity2), srcv(jpr_itx2)%clgrid, 'en->j', zty )    
     953                  CALL rot_rep( frcv(jpr_itx2)%z3(:,:,1), frcv(jpr_ity2)%z3(:,:,1), srcv(jpr_itx2)%clgrid, 'en->j', zty )    
    904954               ELSE 
    905                   CALL rot_rep( frcv(:,:,jpr_itx1), frcv(:,:,jpr_ity1), srcv(jpr_itx1)%clgrid, 'en->j', zty )   
     955                  CALL rot_rep( frcv(jpr_itx1)%z3(:,:,1), frcv(jpr_ity1)%z3(:,:,1), srcv(jpr_itx1)%clgrid, 'en->j', zty )   
    906956               ENDIF 
    907                frcv(:,:,jpr_ity1) = zty(:,:)      ! overwrite 2nd component on the 1st grid 
     957               frcv(jpr_ity1)%z3(:,:,1) = zty(:,:)      ! overwrite 2nd component on the 1st grid 
    908958            ENDIF 
    909959            !                                                   ! ======================= ! 
    910960         ELSE                                                   !     use ocean stress    ! 
    911961            !                                                   ! ======================= ! 
    912             frcv(:,:,jpr_itx1) = frcv(:,:,jpr_otx1) 
    913             frcv(:,:,jpr_ity1) = frcv(:,:,jpr_oty1) 
     962            frcv(jpr_itx1)%z3(:,:,1) = frcv(jpr_otx1)%z3(:,:,1) 
     963            frcv(jpr_ity1)%z3(:,:,1) = frcv(jpr_oty1)%z3(:,:,1) 
    914964            ! 
    915965         ENDIF 
     
    934984               DO jj = 2, jpjm1                                   ! (U,V) ==> I 
    935985                  DO ji = 2, jpim1   ! NO vector opt. 
    936                      p_taui(ji,jj) = 0.5 * ( frcv(ji-1,jj  ,jpr_itx1) + frcv(ji-1,jj-1,jpr_itx1) ) 
    937                      p_tauj(ji,jj) = 0.5 * ( frcv(ji  ,jj-1,jpr_ity1) + frcv(ji-1,jj-1,jpr_ity1) ) 
     986                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji-1,jj  ,1) + frcv(jpr_itx1)%z3(ji-1,jj-1,1) ) 
     987                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji  ,jj-1,1) + frcv(jpr_ity1)%z3(ji-1,jj-1,1) ) 
    938988                  END DO 
    939989               END DO 
     
    941991               DO jj = 2, jpjm1                                   ! F ==> I 
    942992                  DO ji = 2, jpim1   ! NO vector opt. 
    943                      p_taui(ji,jj) = frcv(ji-1,jj-1,jpr_itx1)  
    944                      p_tauj(ji,jj) = frcv(ji-1,jj-1,jpr_ity1)   
     993                     p_taui(ji,jj) = frcv(jpr_itx1)%z3(ji-1,jj-1,1) 
     994                     p_tauj(ji,jj) = frcv(jpr_ity1)%z3(ji-1,jj-1,1) 
    945995                  END DO 
    946996               END DO 
     
    948998               DO jj = 2, jpjm1                                   ! T ==> I 
    949999                  DO ji = 2, jpim1   ! NO vector opt. 
    950                      p_taui(ji,jj) = 0.25 * ( frcv(ji,jj  ,jpr_itx1) + frcv(ji-1,jj  ,jpr_itx1)   & 
    951                         &                   + frcv(ji,jj-1,jpr_itx1) + frcv(ji-1,jj-1,jpr_itx1) )  
    952                      p_tauj(ji,jj) = 0.25 * ( frcv(ji,jj  ,jpr_ity1) + frcv(ji-1,jj  ,jpr_ity1)   & 
    953                         &                   + frcv(ji,jj-1,jpr_ity1) + frcv(ji-1,jj-1,jpr_ity1) ) 
     1000                     p_taui(ji,jj) = 0.25 * ( frcv(jpr_itx1)%z3(ji,jj  ,1) + frcv(jpr_itx1)%z3(ji-1,jj  ,1)   & 
     1001                        &                   + frcv(jpr_itx1)%z3(ji,jj-1,1) + frcv(jpr_itx1)%z3(ji-1,jj-1,1) )  
     1002                     p_tauj(ji,jj) = 0.25 * ( frcv(jpr_ity1)%z3(ji,jj  ,1) + frcv(jpr_ity1)%z3(ji-1,jj  ,1)   & 
     1003                        &                   + frcv(jpr_oty1)%z3(ji,jj-1,1) + frcv(jpr_ity1)%z3(ji-1,jj-1,1) ) 
    9541004                  END DO 
    9551005               END DO 
    9561006            CASE( 'I' ) 
    957                p_taui(:,:) = frcv(:,:,jpr_itx1)                   ! I ==> I 
    958                p_tauj(:,:) = frcv(:,:,jpr_ity1) 
     1007               p_taui(:,:) = frcv(jpr_itx1)%z3(:,:,1)                   ! I ==> I 
     1008               p_tauj(:,:) = frcv(jpr_ity1)%z3(:,:,1) 
    9591009            END SELECT 
    9601010            IF( srcv(jpr_itx1)%clgrid /= 'I' ) THEN  
     
    9671017               DO jj = 2, jpjm1                                   ! (U,V) ==> F 
    9681018                  DO ji = fs_2, fs_jpim1   ! vector opt. 
    969                      p_taui(ji,jj) = 0.5 * ( frcv(ji,jj,jpr_itx1) + frcv(ji  ,jj+1,jpr_itx1) ) 
    970                      p_tauj(ji,jj) = 0.5 * ( frcv(ji,jj,jpr_ity1) + frcv(ji+1,jj  ,jpr_ity1) ) 
     1019                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji,jj,1) + frcv(jpr_itx1)%z3(ji  ,jj+1,1) ) 
     1020                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji,jj,1) + frcv(jpr_ity1)%z3(ji+1,jj  ,1) ) 
    9711021                  END DO 
    9721022               END DO 
     
    9741024               DO jj = 2, jpjm1                                   ! I ==> F 
    9751025                  DO ji = 2, jpim1   ! NO vector opt. 
    976                      p_taui(ji,jj) = frcv(ji+1,jj+1,jpr_itx1)  
    977                      p_tauj(ji,jj) = frcv(ji+1,jj+1,jpr_ity1)   
     1026                     p_taui(ji,jj) = frcv(jpr_itx1)%z3(ji+1,jj+1,1) 
     1027                     p_tauj(ji,jj) = frcv(jpr_ity1)%z3(ji+1,jj+1,1) 
    9781028                  END DO 
    9791029               END DO 
     
    9811031               DO jj = 2, jpjm1                                   ! T ==> F 
    9821032                  DO ji = 2, jpim1   ! NO vector opt. 
    983                      p_taui(ji,jj) = 0.25 * ( frcv(ji,jj  ,jpr_itx1) + frcv(ji+1,jj  ,jpr_itx1)   & 
    984                         &                   + frcv(ji,jj+1,jpr_itx1) + frcv(ji+1,jj+1,jpr_itx1) )  
    985                      p_tauj(ji,jj) = 0.25 * ( frcv(ji,jj  ,jpr_ity1) + frcv(ji+1,jj  ,jpr_ity1)   & 
    986                         &                   + frcv(ji,jj+1,jpr_ity1) + frcv(ji+1,jj+1,jpr_ity1) ) 
     1033                     p_taui(ji,jj) = 0.25 * ( frcv(jpr_itx1)%z3(ji,jj  ,1) + frcv(jpr_itx1)%z3(ji+1,jj  ,1)   & 
     1034                        &                   + frcv(jpr_itx1)%z3(ji,jj+1,1) + frcv(jpr_itx1)%z3(ji+1,jj+1,1) )  
     1035                     p_tauj(ji,jj) = 0.25 * ( frcv(jpr_ity1)%z3(ji,jj  ,1) + frcv(jpr_ity1)%z3(ji+1,jj  ,1)   & 
     1036                        &                   + frcv(jpr_ity1)%z3(ji,jj+1,1) + frcv(jpr_ity1)%z3(ji+1,jj+1,1) ) 
    9871037                  END DO 
    9881038               END DO 
    9891039            CASE( 'F' ) 
    990                p_taui(:,:) = frcv(:,:,jpr_itx1)                   ! F ==> F 
    991                p_tauj(:,:) = frcv(:,:,jpr_ity1) 
     1040               p_taui(:,:) = frcv(jpr_itx1)%z3(:,:,1)                   ! F ==> F 
     1041               p_tauj(:,:) = frcv(jpr_ity1)%z3(:,:,1) 
    9921042            END SELECT 
    9931043            IF( srcv(jpr_itx1)%clgrid /= 'F' ) THEN  
     
    9981048            SELECT CASE ( srcv(jpr_itx1)%clgrid ) 
    9991049            CASE( 'U' ) 
    1000                p_taui(:,:) = frcv(:,:,jpr_itx1)                   ! (U,V) ==> (U,V) 
    1001                p_tauj(:,:) = frcv(:,:,jpr_ity1) 
     1050               p_taui(:,:) = frcv(jpr_itx1)%z3(:,:,1)                   ! (U,V) ==> (U,V) 
     1051               p_tauj(:,:) = frcv(jpr_ity1)%z3(:,:,1) 
    10021052            CASE( 'F' ) 
    10031053               DO jj = 2, jpjm1                                   ! F ==> (U,V) 
    10041054                  DO ji = fs_2, fs_jpim1   ! vector opt. 
    1005                      p_taui(ji,jj) = 0.5 * ( frcv(ji,jj,jpr_itx1) + frcv(ji  ,jj-1,jpr_itx1) ) 
    1006                      p_tauj(ji,jj) = 0.5 * ( frcv(ji,jj,jpr_ity1) + frcv(ji-1,jj  ,jpr_ity1) ) 
     1055                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji,jj,1) + frcv(jpr_itx1)%z3(ji  ,jj-1,1) ) 
     1056                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(jj,jj,1) + frcv(jpr_ity1)%z3(ji-1,jj  ,1) ) 
    10071057                  END DO 
    10081058               END DO 
     
    10101060               DO jj = 2, jpjm1                                   ! T ==> (U,V) 
    10111061                  DO ji = fs_2, fs_jpim1   ! vector opt. 
    1012                      p_taui(ji,jj) = 0.5 * ( frcv(ji+1,jj  ,jpr_itx1) + frcv(ji,jj,jpr_itx1) ) 
    1013                      p_tauj(ji,jj) = 0.5 * ( frcv(ji  ,jj+1,jpr_ity1) + frcv(ji,jj,jpr_ity1) ) 
     1062                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji+1,jj  ,1) + frcv(jpr_itx1)%z3(ji,jj,1) ) 
     1063                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji  ,jj+1,1) + frcv(jpr_ity1)%z3(ji,jj,1) ) 
    10141064                  END DO 
    10151065               END DO 
     
    10171067               DO jj = 2, jpjm1                                   ! I ==> (U,V) 
    10181068                  DO ji = 2, jpim1   ! NO vector opt. 
    1019                      p_taui(ji,jj) = 0.5 * ( frcv(ji+1,jj+1,jpr_itx1) + frcv(ji+1,jj  ,jpr_itx1) ) 
    1020                      p_tauj(ji,jj) = 0.5 * ( frcv(ji+1,jj+1,jpr_ity1) + frcv(ji  ,jj+1,jpr_ity1) ) 
     1069                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji+1,jj+1,1) + frcv(jpr_itx1)%z3(ji+1,jj  ,1) ) 
     1070                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji+1,jj+1,1) + frcv(jpr_ity1)%z3(ji  ,jj+1,1) ) 
    10211071                  END DO 
    10221072               END DO 
     
    10271077         END SELECT 
    10281078 
    1029          !!gm Should be useless as sbc_cpl_ice_tau only called at coupled frequency 
    1030          ! The receive stress are transformed such that in all case frcv(:,:,jpr_itx1), frcv(:,:,jpr_ity1) 
    1031          ! become the i-component and j-component of the stress at the right grid point  
    1032          !!gm  frcv(:,:,jpr_itx1) = p_taui(:,:) 
    1033          !!gm  frcv(:,:,jpr_ity1) = p_tauj(:,:) 
    1034          !!gm 
    10351079      ENDIF 
    10361080      !    
     
    10401084    
    10411085 
    1042    SUBROUTINE sbc_cpl_ice_flx( p_frld  ,                                  & 
    1043       &                        pqns_tot, pqns_ice, pqsr_tot , pqsr_ice,   & 
    1044       &                        pemp_tot, pemp_ice, pdqns_ice, psprecip,   & 
    1045       &                        palbi   , psst    , pist                 ) 
     1086   SUBROUTINE sbc_cpl_ice_flx( p_frld  , palbi   , psst    , pist    ) 
    10461087      !!---------------------------------------------------------------------- 
    1047       !!             ***  ROUTINE sbc_cpl_ice_flx_rcv  *** 
     1088      !!             ***  ROUTINE sbc_cpl_ice_flx  *** 
    10481089      !! 
    10491090      !! ** Purpose :   provide the heat and freshwater fluxes of the  
     
    10661107      !!             the atmosphere 
    10671108      !! 
    1068       !!             N.B. - fields over sea-ice are passed in argument so that 
    1069       !!                 the module can be compile without sea-ice. 
    10701109      !!                  - the fluxes have been separated from the stress as 
    10711110      !!                 (a) they are updated at each ice time step compare to 
     
    10781117      !! 
    10791118      !! ** Action  :   update at each nf_ice time step: 
    1080       !!                   pqns_tot, pqsr_tot  non-solar and solar total heat fluxes 
    1081       !!                   pqns_ice, pqsr_ice  non-solar and solar heat fluxes over the ice 
    1082       !!                   pemp_tot            total evaporation - precipitation(liquid and solid) (-runoff)(-calving) 
    1083       !!                   pemp_ice            ice sublimation - solid precipitation over the ice 
    1084       !!                   pdqns_ice           d(non-solar heat flux)/d(Temperature) over the ice 
     1119      !!                   qns_tot, qsr_tot  non-solar and solar total heat fluxes 
     1120      !!                   qns_ice, qsr_ice  non-solar and solar heat fluxes over the ice 
     1121      !!                   emp_tot            total evaporation - precipitation(liquid and solid) (-runoff)(-calving) 
     1122      !!                   emp_ice            ice sublimation - solid precipitation over the ice 
     1123      !!                   dqns_ice           d(non-solar heat flux)/d(Temperature) over the ice 
    10851124      !!                   sprecip             solid precipitation over the ocean   
    10861125      !!---------------------------------------------------------------------- 
    10871126      USE wrk_nemo, ONLY:   wrk_in_use, wrk_not_released 
    1088       USE wrk_nemo, ONLY:   zcptn  => wrk_2d_1   ! rcp * tn(:,:,1) 
    1089       USE wrk_nemo, ONLY:   ztmp   => wrk_2d_2   ! temporary array 
    1090       USE wrk_nemo, ONLY:   zsnow  => wrk_2d_3   ! snow precipitation  
    1091       USE wrk_nemo, ONLY:   zicefr => wrk_3d_4   ! ice fraction  
    1092       !! 
    1093       REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   p_frld     ! lead fraction                [0 to 1] 
    1094       REAL(wp), INTENT(  out), DIMENSION(:,:  ) ::   pqns_tot   ! total non solar heat flux    [W/m2] 
    1095       REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   pqns_ice   ! ice   non solar heat flux    [W/m2] 
    1096       REAL(wp), INTENT(  out), DIMENSION(:,:  ) ::   pqsr_tot   ! total     solar heat flux    [W/m2] 
    1097       REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   pqsr_ice   ! ice       solar heat flux    [W/m2] 
    1098       REAL(wp), INTENT(  out), DIMENSION(:,:  ) ::   pemp_tot   ! total     freshwater budget        [Kg/m2/s] 
    1099       REAL(wp), INTENT(  out), DIMENSION(:,:  ) ::   pemp_ice   ! solid freshwater budget over ice   [Kg/m2/s] 
    1100       REAL(wp), INTENT(  out), DIMENSION(:,:  ) ::   psprecip   ! Net solid precipitation (=emp_ice) [Kg/m2/s] 
    1101       REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   pdqns_ice  ! d(Q non solar)/d(Temperature) over ice 
     1127      USE wrk_nemo, ONLY:   zcptn  => wrk_2d_2   ! rcp * tn(:,:,1) 
     1128      USE wrk_nemo, ONLY:   ztmp   => wrk_2d_3   ! temporary array 
     1129      USE wrk_nemo, ONLY:   zicefr => wrk_2d_4   ! ice fraction  
     1130      !! 
     1131      REAL(wp), INTENT(in   ), DIMENSION(:,:)   ::   p_frld     ! lead fraction                [0 to 1] 
    11021132      ! optional arguments, used only in 'mixed oce-ice' case 
    11031133      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   palbi   ! ice albedo  
    11041134      REAL(wp), INTENT(in   ), DIMENSION(:,:  ), OPTIONAL ::   psst    ! sea surface temperature     [Celcius] 
    11051135      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   pist    ! ice surface temperature     [Kelvin] 
    1106       !! 
    1107       INTEGER ::   ji, jj           ! dummy loop indices 
    1108       INTEGER ::   isec, info       ! temporary integer 
    1109       REAL(wp)::   zcoef, ztsurf    ! temporary scalar 
     1136      ! 
     1137      INTEGER ::   jl   ! dummy loop index 
    11101138      !!---------------------------------------------------------------------- 
    11111139 
    1112       IF( wrk_in_use(2, 1,2,3) .OR. wrk_in_use(3, 4) ) THEN 
     1140      IF( wrk_in_use(2, 2,3,4) ) THEN 
    11131141         CALL ctl_stop('sbc_cpl_ice_flx: requested workspace arrays unavailable')   ;   RETURN 
    11141142      ENDIF 
    11151143 
    1116       zicefr(:,:,1) = 1.- p_frld(:,:,1) 
    1117       IF( lk_diaar5 )   zcptn(:,:) = rcp * tn(:,:,1) 
     1144      zicefr(:,:) = 1.- p_frld(:,:) 
     1145      IF( lk_diaar5 )   zcptn(:,:) = rcp * tsn(:,:,1,1) 
    11181146      ! 
    11191147      !                                                      ! ========================= ! 
     
    11241152      !                                                           ! solid precipitation  - sublimation       (emp_ice) 
    11251153      !                                                           ! solid Precipitation                      (sprecip) 
    1126       SELECT CASE( TRIM( cn_rcv_emp ) ) 
     1154      SELECT CASE( TRIM( sn_rcv_emp%cldes ) ) 
    11271155      CASE( 'conservative'  )   ! received fields: jpr_rain, jpr_snow, jpr_ievp, jpr_tevp 
    1128          pemp_tot(:,:) = frcv(:,:,jpr_tevp) - frcv(:,:,jpr_rain) - frcv(:,:,jpr_snow) 
    1129          pemp_ice(:,:) = frcv(:,:,jpr_ievp) - frcv(:,:,jpr_snow) 
    1130          zsnow   (:,:) = frcv(:,:,jpr_snow) 
    1131                            CALL iom_put( 'rain'         , frcv(:,:,jpr_rain)              )   ! liquid precipitation  
    1132          IF( lk_diaar5 )   CALL iom_put( 'hflx_rain_cea', frcv(:,:,jpr_rain) * zcptn(:,:) )   ! heat flux from liq. precip.  
    1133          ztmp(:,:) = frcv(:,:,jpr_tevp) - frcv(:,:,jpr_ievp) * zicefr(:,:,1) 
     1156         sprecip(:,:) = frcv(jpr_snow)%z3(:,:,1)                 ! May need to ensure positive here 
     1157         tprecip(:,:) = frcv(jpr_rain)%z3(:,:,1) + sprecip (:,:) ! May need to ensure positive here 
     1158         emp_tot(:,:) = frcv(jpr_tevp)%z3(:,:,1) - tprecip(:,:) 
     1159         emp_ice(:,:) = frcv(jpr_ievp)%z3(:,:,1) - frcv(jpr_snow)%z3(:,:,1) 
     1160                           CALL iom_put( 'rain'         , frcv(jpr_rain)%z3(:,:,1)              )   ! liquid precipitation  
     1161         IF( lk_diaar5 )   CALL iom_put( 'hflx_rain_cea', frcv(jpr_rain)%z3(:,:,1) * zcptn(:,:) )   ! heat flux from liq. precip.  
     1162         ztmp(:,:) = frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) 
    11341163                           CALL iom_put( 'evap_ao_cea'  , ztmp                            )   ! ice-free oce evap (cell average) 
    11351164         IF( lk_diaar5 )   CALL iom_put( 'hflx_evap_cea', ztmp(:,:         ) * zcptn(:,:) )   ! heat flux from from evap (cell ave) 
    1136       CASE( 'oce and ice'   )   ! received fields: jpr_sbpr, jpr_semp, jpr_oemp 
    1137          pemp_tot(:,:) = p_frld(:,:,1) * frcv(:,:,jpr_oemp) + zicefr(:,:,1) * frcv(:,:,jpr_sbpr)  
    1138          pemp_ice(:,:) = frcv(:,:,jpr_semp) 
    1139          zsnow   (:,:) = - frcv(:,:,jpr_semp) + frcv(:,:,jpr_ievp) 
     1165      CASE( 'oce and ice'   )   ! received fields: jpr_sbpr, jpr_semp, jpr_oemp, jpr_ievp 
     1166         emp_tot(:,:) = p_frld(:,:) * frcv(jpr_oemp)%z3(:,:,1) + zicefr(:,:) * frcv(jpr_sbpr)%z3(:,:,1) 
     1167         emp_ice(:,:) = frcv(jpr_semp)%z3(:,:,1) 
     1168         sprecip(:,:) = - frcv(jpr_semp)%z3(:,:,1) + frcv(jpr_ievp)%z3(:,:,1) 
    11401169      END SELECT 
    1141       psprecip(:,:) = - pemp_ice(:,:) 
    1142       CALL iom_put( 'snowpre'    , zsnow                               )   ! Snow 
    1143       CALL iom_put( 'snow_ao_cea', zsnow(:,:         ) * p_frld(:,:,1) )   ! Snow        over ice-free ocean  (cell average) 
    1144       CALL iom_put( 'snow_ai_cea', zsnow(:,:         ) * zicefr(:,:,1) )   ! Snow        over sea-ice         (cell average) 
    1145       CALL iom_put( 'subl_ai_cea', frcv (:,:,jpr_ievp) * zicefr(:,:,1) )   ! Sublimation over sea-ice         (cell average) 
     1170 
     1171      CALL iom_put( 'snowpre'    , sprecip                                )   ! Snow 
     1172      CALL iom_put( 'snow_ao_cea', sprecip(:,:         ) * p_frld(:,:)    )   ! Snow        over ice-free ocean  (cell average) 
     1173      CALL iom_put( 'snow_ai_cea', sprecip(:,:         ) * zicefr(:,:)    )   ! Snow        over sea-ice         (cell average) 
     1174      CALL iom_put( 'subl_ai_cea', frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) )   ! Sublimation over sea-ice         (cell average) 
    11461175      !    
    11471176      !                                                           ! runoffs and calving (put in emp_tot) 
    11481177      IF( srcv(jpr_rnf)%laction ) THEN  
    1149          pemp_tot(:,:) = pemp_tot(:,:) - frcv(:,:,jpr_rnf) 
    1150                            CALL iom_put( 'runoffs'      , frcv(:,:,jpr_rnf )              )   ! rivers 
    1151          IF( lk_diaar5 )   CALL iom_put( 'hflx_rnf_cea' , frcv(:,:,jpr_rnf ) * zcptn(:,:) )   ! heat flux from rivers 
     1178         emp_tot(:,:) = emp_tot(:,:) - frcv(jpr_rnf)%z3(:,:,1) 
     1179                           CALL iom_put( 'runoffs'      , frcv(jpr_rnf)%z3(:,:,1)              )   ! rivers 
     1180         IF( lk_diaar5 )   CALL iom_put( 'hflx_rnf_cea' , frcv(jpr_rnf)%z3(:,:,1) * zcptn(:,:) )   ! heat flux from rivers 
    11521181      ENDIF 
    11531182      IF( srcv(jpr_cal)%laction ) THEN  
    1154          pemp_tot(:,:) = pemp_tot(:,:) - frcv(:,:,jpr_cal) 
    1155          CALL iom_put( 'calving', frcv(:,:,jpr_cal) ) 
     1183         emp_tot(:,:) = emp_tot(:,:) - frcv(jpr_cal)%z3(:,:,1) 
     1184         CALL iom_put( 'calving', frcv(jpr_cal)%z3(:,:,1) ) 
    11561185      ENDIF 
    11571186      ! 
     
    11591188!!gm                                       at least should be optional... 
    11601189!!       ! remove negative runoff                            ! sum over the global domain 
    1161 !!       zcumulpos = SUM( MAX( frcv(:,:,jpr_rnf), 0.e0 ) * e1t(:,:) * e2t(:,:) * tmask_i(:,:) )  
    1162 !!       zcumulneg = SUM( MIN( frcv(:,:,jpr_rnf), 0.e0 ) * e1t(:,:) * e2t(:,:) * tmask_i(:,:) ) 
     1190!!       zcumulpos = SUM( MAX( frcv(jpr_rnf)%z3(:,:,1), 0.e0 ) * e1t(:,:) * e2t(:,:) * tmask_i(:,:) )  
     1191!!       zcumulneg = SUM( MIN( frcv(jpr_rnf)%z3(:,:,1), 0.e0 ) * e1t(:,:) * e2t(:,:) * tmask_i(:,:) ) 
    11631192!!       IF( lk_mpp )   CALL mpp_sum( zcumulpos ) 
    11641193!!       IF( lk_mpp )   CALL mpp_sum( zcumulneg )  
    11651194!!       IF( zcumulpos /= 0. ) THEN                          ! distribute negative runoff on positive runoff grid points 
    11661195!!          zcumulneg = 1.e0 + zcumulneg / zcumulpos 
    1167 !!          frcv(:,:,jpr_rnf) = MAX( frcv(:,:,jpr_rnf), 0.e0 ) * zcumulneg 
     1196!!          frcv(jpr_rnf)%z3(:,:,1) = MAX( frcv(jpr_rnf)%z3(:,:,1), 0.e0 ) * zcumulneg 
    11681197!!       ENDIF      
    1169 !!       pemp_tot(:,:) = pemp_tot(:,:) - frcv(:,:,jpr_rnf)   ! add runoff to e-p  
     1198!!       emp_tot(:,:) = emp_tot(:,:) - frcv(jpr_rnf)%z3(:,:,1)   ! add runoff to e-p  
    11701199!! 
    11711200!!gm  end of internal cooking 
    11721201 
    1173  
    11741202      !                                                      ! ========================= ! 
    1175       SELECT CASE( TRIM( cn_rcv_qns ) )                      !   non solar heat fluxes   !   (qns) 
     1203      SELECT CASE( TRIM( sn_rcv_qns%cldes ) )                !   non solar heat fluxes   !   (qns) 
    11761204      !                                                      ! ========================= ! 
     1205      CASE( 'oce only' )                                     ! the required field is directly provided 
     1206         qns_tot(:,:  ) = frcv(jpr_qnsoce)%z3(:,:,1) 
    11771207      CASE( 'conservative' )                                      ! the required fields are directly provided 
    1178          pqns_tot(:,:  ) = frcv(:,:,jpr_qnsmix) 
    1179          pqns_ice(:,:,1) = frcv(:,:,jpr_qnsice) 
     1208         qns_tot(:,:  ) = frcv(jpr_qnsmix)%z3(:,:,1) 
     1209         IF ( TRIM(sn_rcv_qns%clcat) == 'yes' ) THEN 
     1210            qns_ice(:,:,1:jpl) = frcv(jpr_qnsice)%z3(:,:,1:jpl) 
     1211         ELSE 
     1212            ! Set all category values equal for the moment 
     1213            DO jl=1,jpl 
     1214               qns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,1) 
     1215            ENDDO 
     1216         ENDIF 
    11801217      CASE( 'oce and ice' )       ! the total flux is computed from ocean and ice fluxes 
    1181          pqns_tot(:,:  ) =  p_frld(:,:,1) * frcv(:,:,jpr_qnsoce) + zicefr(:,:,1) * frcv(:,:,jpr_qnsice) 
    1182          pqns_ice(:,:,1) =  frcv(:,:,jpr_qnsice) 
     1218         qns_tot(:,:  ) =  p_frld(:,:) * frcv(jpr_qnsoce)%z3(:,:,1) 
     1219         IF ( TRIM(sn_rcv_qns%clcat) == 'yes' ) THEN 
     1220            DO jl=1,jpl 
     1221               qns_tot(:,:   ) = qns_tot(:,:) + a_i(:,:,jl) * frcv(jpr_qnsice)%z3(:,:,jl)    
     1222               qns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,jl) 
     1223            ENDDO 
     1224         ELSE 
     1225            DO jl=1,jpl 
     1226               qns_tot(:,:   ) = qns_tot(:,:) + zicefr(:,:) * frcv(jpr_qnsice)%z3(:,:,1) 
     1227               qns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,1) 
     1228            ENDDO 
     1229         ENDIF 
    11831230      CASE( 'mixed oce-ice' )     ! the ice flux is cumputed from the total flux, the SST and ice informations 
    1184          pqns_tot(:,:  ) = frcv(:,:,jpr_qnsmix) 
    1185          pqns_ice(:,:,1) = frcv(:,:,jpr_qnsmix)    & 
    1186             &            + frcv(:,:,jpr_dqnsdt) * ( pist(:,:,1) - ( (rt0 + psst(:,:  ) ) * p_frld(:,:,1)   & 
    1187             &                                                   +          pist(:,:,1)   * zicefr(:,:,1) ) ) 
     1231! ** NEED TO SORT OUT HOW THIS SHOULD WORK IN THE MULTI-CATEGORY CASE - CURRENTLY NOT ALLOWED WHEN INTERFACE INITIALISED ** 
     1232         qns_tot(:,:  ) = frcv(jpr_qnsmix)%z3(:,:,1) 
     1233         qns_ice(:,:,1) = frcv(jpr_qnsmix)%z3(:,:,1)    & 
     1234            &            + frcv(jpr_dqnsdt)%z3(:,:,1) * ( pist(:,:,1) - ( (rt0 + psst(:,:  ) ) * p_frld(:,:)   & 
     1235            &                                                   +          pist(:,:,1)   * zicefr(:,:) ) ) 
    11881236      END SELECT 
    1189       ztmp(:,:) = p_frld(:,:,1) * zsnow(:,:) * lfus               ! add the latent heat of solid precip. melting 
    1190       pqns_tot(:,:) = pqns_tot(:,:) - ztmp(:,:)                   ! over free ocean  
    1191       IF( lk_diaar5 )   CALL iom_put( 'hflx_snow_cea', ztmp + zsnow(:,:) * zcptn(:,:) )   ! heat flux from snow (cell average) 
     1237      ztmp(:,:) = p_frld(:,:) * sprecip(:,:) * lfus               ! add the latent heat of solid precip. melting 
     1238      qns_tot(:,:) = qns_tot(:,:) - ztmp(:,:)                     ! over free ocean  
     1239      IF( lk_diaar5 )   CALL iom_put( 'hflx_snow_cea', ztmp + sprecip(:,:) * zcptn(:,:) )   ! heat flux from snow (cell average) 
    11921240!!gm 
    11931241!!    currently it is taken into account in leads budget but not in the qns_tot, and thus not in  
     
    11991247      !                                      
    12001248      IF( srcv(jpr_cal)%laction ) THEN                            ! Iceberg melting  
    1201          ztmp(:,:) = frcv(:,:,jpr_cal) * lfus                     ! add the latent heat of iceberg melting  
    1202          pqns_tot(:,:) = pqns_tot(:,:) - ztmp(:,:) 
    1203          IF( lk_diaar5 )   CALL iom_put( 'hflx_cal_cea', ztmp + frcv(:,:,jpr_cal) * zcptn(:,:) )   ! heat flux from calving 
     1249         ztmp(:,:) = frcv(jpr_cal)%z3(:,:,1) * lfus               ! add the latent heat of iceberg melting  
     1250         qns_tot(:,:) = qns_tot(:,:) - ztmp(:,:) 
     1251         IF( lk_diaar5 )   CALL iom_put( 'hflx_cal_cea', ztmp + frcv(jpr_cal)%z3(:,:,1) * zcptn(:,:) )   ! heat flux from calving 
    12041252      ENDIF 
    12051253 
    12061254      !                                                      ! ========================= ! 
    1207       SELECT CASE( TRIM( cn_rcv_qsr ) )                      !      solar heat fluxes    !   (qsr) 
     1255      SELECT CASE( TRIM( sn_rcv_qsr%cldes ) )                !      solar heat fluxes    !   (qsr) 
    12081256      !                                                      ! ========================= ! 
     1257      CASE( 'oce only' ) 
     1258         qsr_tot(:,:  ) = MAX(0.0,frcv(jpr_qsroce)%z3(:,:,1)) 
    12091259      CASE( 'conservative' ) 
    1210          pqsr_tot(:,:  ) = frcv(:,:,jpr_qsrmix) 
    1211          pqsr_ice(:,:,1) = frcv(:,:,jpr_qsrice) 
     1260         qsr_tot(:,:  ) = frcv(jpr_qsrmix)%z3(:,:,1) 
     1261         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN 
     1262            qsr_ice(:,:,1:jpl) = frcv(jpr_qsrice)%z3(:,:,1:jpl) 
     1263         ELSE 
     1264            ! Set all category values equal for the moment 
     1265            DO jl=1,jpl 
     1266               qsr_ice(:,:,jl) = frcv(jpr_qsrice)%z3(:,:,1) 
     1267            ENDDO 
     1268         ENDIF 
     1269         qsr_tot(:,:  ) = frcv(jpr_qsrmix)%z3(:,:,1) 
     1270         qsr_ice(:,:,1) = frcv(jpr_qsrice)%z3(:,:,1) 
    12121271      CASE( 'oce and ice' ) 
    1213          pqsr_tot(:,:  ) =  p_frld(:,:,1) * frcv(:,:,jpr_qsroce) + zicefr(:,:,1) * frcv(:,:,jpr_qsrice) 
    1214          pqsr_ice(:,:,1) =  frcv(:,:,jpr_qsrice) 
     1272         qsr_tot(:,:  ) =  p_frld(:,:) * frcv(jpr_qsroce)%z3(:,:,1) 
     1273         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN 
     1274            DO jl=1,jpl 
     1275               qsr_tot(:,:   ) = qsr_tot(:,:) + a_i(:,:,jl) * frcv(jpr_qsrice)%z3(:,:,jl)    
     1276               qsr_ice(:,:,jl) = frcv(jpr_qsrice)%z3(:,:,jl) 
     1277            ENDDO 
     1278         ELSE 
     1279            DO jl=1,jpl 
     1280               qsr_tot(:,:   ) = qsr_tot(:,:) + zicefr(:,:) * frcv(jpr_qsrice)%z3(:,:,1) 
     1281               qsr_ice(:,:,jl) = frcv(jpr_qsrice)%z3(:,:,1) 
     1282            ENDDO 
     1283         ENDIF 
    12151284      CASE( 'mixed oce-ice' ) 
    1216          pqsr_tot(:,:  ) = frcv(:,:,jpr_qsrmix) 
     1285         qsr_tot(:,:  ) = frcv(jpr_qsrmix)%z3(:,:,1) 
     1286! ** NEED TO SORT OUT HOW THIS SHOULD WORK IN THE MULTI-CATEGORY CASE - CURRENTLY NOT ALLOWED WHEN INTERFACE INITIALISED ** 
    12171287!       Create solar heat flux over ice using incoming solar heat flux and albedos 
    12181288!       ( see OASIS3 user guide, 5th edition, p39 ) 
    1219          pqsr_ice(:,:,1) = frcv(:,:,jpr_qsrmix) * ( 1.- palbi(:,:,1) )   & 
    1220             &            / (  1.- ( albedo_oce_mix(:,:  ) * p_frld(:,:,1)   & 
    1221             &                     + palbi         (:,:,1) * zicefr(:,:,1) ) ) 
     1289         qsr_ice(:,:,1) = frcv(jpr_qsrmix)%z3(:,:,1) * ( 1.- palbi(:,:,1) )   & 
     1290            &            / (  1.- ( albedo_oce_mix(:,:  ) * p_frld(:,:)       & 
     1291            &                     + palbi         (:,:,1) * zicefr(:,:) ) ) 
    12221292      END SELECT 
    12231293      IF( ln_dm2dc ) THEN   ! modify qsr to include the diurnal cycle 
    1224          pqsr_tot(:,:  ) = sbc_dcy( pqsr_tot(:,:  ) ) 
    1225          pqsr_ice(:,:,1) = sbc_dcy( pqsr_ice(:,:,1) ) 
    1226       ENDIF 
    1227  
    1228       SELECT CASE( TRIM( cn_rcv_dqnsdt ) ) 
     1294         qsr_tot(:,:  ) = sbc_dcy( qsr_tot(:,:  ) ) 
     1295         DO jl=1,jpl 
     1296            qsr_ice(:,:,jl) = sbc_dcy( qsr_ice(:,:,jl) ) 
     1297         ENDDO 
     1298      ENDIF 
     1299 
     1300      SELECT CASE( TRIM( sn_rcv_dqnsdt%cldes ) ) 
    12291301      CASE ('coupled') 
    1230           pdqns_ice(:,:,1) = frcv(:,:,jpr_dqnsdt) 
     1302         IF ( TRIM(sn_rcv_dqnsdt%clcat) == 'yes' ) THEN 
     1303            dqns_ice(:,:,1:jpl) = frcv(jpr_dqnsdt)%z3(:,:,1:jpl) 
     1304         ELSE 
     1305            ! Set all category values equal for the moment 
     1306            DO jl=1,jpl 
     1307               dqns_ice(:,:,jl) = frcv(jpr_dqnsdt)%z3(:,:,1) 
     1308            ENDDO 
     1309         ENDIF 
    12311310      END SELECT 
    12321311 
    1233       IF( wrk_not_released(2, 1,2,3)  .OR.   & 
    1234           wrk_not_released(3, 4)      )   CALL ctl_stop('sbc_cpl_ice_flx: failed to release workspace arrays') 
     1312      SELECT CASE( TRIM( sn_rcv_iceflx%cldes ) ) 
     1313      CASE ('coupled') 
     1314         topmelt(:,:,:)=frcv(jpr_topm)%z3(:,:,:) 
     1315         botmelt(:,:,:)=frcv(jpr_botm)%z3(:,:,:) 
     1316      END SELECT 
     1317 
     1318      IF( wrk_not_released(2, 2,3,4) ) CALL ctl_stop('sbc_cpl_ice_flx: failed to release workspace arrays') 
    12351319      ! 
    12361320   END SUBROUTINE sbc_cpl_ice_flx 
     
    12491333      USE wrk_nemo, ONLY:   zfr_l => wrk_2d_1   ! 1. - fr_i(:,:) 
    12501334      USE wrk_nemo, ONLY:   ztmp1 => wrk_2d_2 , ztmp2 => wrk_2d_3 
     1335      USE wrk_nemo, ONLY:   ztmp3 => wrk_3d_1 , ztmp4 => wrk_3d_2 
    12511336      USE wrk_nemo, ONLY:   zotx1 => wrk_2d_4 , zoty1 => wrk_2d_5 , zotz1 => wrk_2d_6 
    12521337      USE wrk_nemo, ONLY:   zitx1 => wrk_2d_7 , zity1 => wrk_2d_8 , zitz1 => wrk_2d_9 
     
    12541339      INTEGER, INTENT(in) ::   kt 
    12551340      ! 
    1256       INTEGER ::   ji, jj       ! dummy loop indices 
     1341      INTEGER ::   ji, jj, jl   ! dummy loop indices 
    12571342      INTEGER ::   isec, info   ! local integer 
    12581343      !!---------------------------------------------------------------------- 
    12591344 
    1260       IF( wrk_in_use(2, 1,2,3,4,5,6,7,8,9) ) THEN 
     1345      IF( wrk_in_use(2, 1,2,3,4,5,6,7,8,9) .OR. wrk_in_use(3, 1,2)  ) THEN 
    12611346         CALL ctl_stop('sbc_cpl_snd: requested workspace arrays are unavailable')   ;   RETURN 
    12621347      ENDIF 
     
    12691354      !                                                      !    Surface temperature    !   in Kelvin 
    12701355      !                                                      ! ------------------------- ! 
    1271       SELECT CASE( cn_snd_temperature) 
    1272       CASE( 'oce only'             )   ;   ztmp1(:,:) =   tn(:,:,1) + rt0 
    1273       CASE( 'weighted oce and ice' )   ;   ztmp1(:,:) = ( tn(:,:,1) + rt0 ) * zfr_l(:,:)    
    1274                                            ztmp2(:,:) =   tn_ice(:,:,1)     *  fr_i(:,:) 
    1275       CASE( 'mixed oce-ice'        )   ;   ztmp1(:,:) = ( tn(:,:,1) + rt0 ) * zfr_l(:,:) + tn_ice(:,:,1) * fr_i(:,:) 
    1276       CASE default                     ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of cn_snd_temperature' ) 
     1356      SELECT CASE( sn_snd_temp%cldes) 
     1357      CASE( 'oce only'             )   ;   ztmp1(:,:) =   tsn(:,:,1,1) + rt0 
     1358      CASE( 'weighted oce and ice' )   ;   ztmp1(:,:) = ( tsn(:,:,1,1) + rt0 ) * zfr_l(:,:)    
     1359         SELECT CASE( sn_snd_temp%clcat ) 
     1360         CASE( 'yes' )    
     1361            ztmp3(:,:,1:jpl) = tn_ice(:,:,1:jpl) * a_i(:,:,1:jpl) 
     1362         CASE( 'no' ) 
     1363            ztmp3(:,:,:) = 0.0 
     1364            DO jl=1,jpl 
     1365               ztmp3(:,:,1) = ztmp3(:,:,1) + tn_ice(:,:,jl) * a_i(:,:,jl) 
     1366            ENDDO 
     1367         CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%clcat' ) 
     1368         END SELECT 
     1369      CASE( 'mixed oce-ice'        )    
     1370         ztmp1(:,:) = ( tsn(:,:,1,1) + rt0 ) * zfr_l(:,:)  
     1371         DO jl=1,jpl 
     1372            ztmp1(:,:) = ztmp1(:,:) + tn_ice(:,:,jl) * a_i(:,:,jl) 
     1373         ENDDO 
     1374      CASE default                     ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%cldes' ) 
    12771375      END SELECT 
    1278       IF( ssnd(jps_toce)%laction )   CALL cpl_prism_snd( jps_toce, isec, ztmp1, info ) 
    1279       IF( ssnd(jps_tice)%laction )   CALL cpl_prism_snd( jps_tice, isec, ztmp2, info ) 
    1280       IF( ssnd(jps_tmix)%laction )   CALL cpl_prism_snd( jps_tmix, isec, ztmp1, info ) 
     1376      IF( ssnd(jps_toce)%laction )   CALL cpl_prism_snd( jps_toce, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info ) 
     1377      IF( ssnd(jps_tice)%laction )   CALL cpl_prism_snd( jps_tice, isec, ztmp3, info ) 
     1378      IF( ssnd(jps_tmix)%laction )   CALL cpl_prism_snd( jps_tmix, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info ) 
    12811379      ! 
    12821380      !                                                      ! ------------------------- ! 
     
    12841382      !                                                      ! ------------------------- ! 
    12851383      IF( ssnd(jps_albice)%laction ) THEN                         ! ice  
    1286          ztmp1(:,:) = alb_ice(:,:,1) * fr_i(:,:) 
    1287          CALL cpl_prism_snd( jps_albice, isec, ztmp1, info ) 
     1384         ztmp3(:,:,1:jpl) = alb_ice(:,:,1:jpl) * a_i(:,:,1:jpl) 
     1385         CALL cpl_prism_snd( jps_albice, isec, ztmp3, info ) 
    12881386      ENDIF 
    12891387      IF( ssnd(jps_albmix)%laction ) THEN                         ! mixed ice-ocean 
    1290          ztmp1(:,:) = albedo_oce_mix(:,:) * zfr_l(:,:) + alb_ice(:,:,1) * fr_i(:,:) 
    1291          CALL cpl_prism_snd( jps_albmix, isec, ztmp1, info ) 
     1388         ztmp1(:,:) = albedo_oce_mix(:,:) * zfr_l(:,:) 
     1389         DO jl=1,jpl 
     1390            ztmp1(:,:) = ztmp1(:,:) + alb_ice(:,:,jl) * a_i(:,:,jl) 
     1391         ENDDO 
     1392         CALL cpl_prism_snd( jps_albmix, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info ) 
    12921393      ENDIF 
    12931394      !                                                      ! ------------------------- ! 
    12941395      !                                                      !  Ice fraction & Thickness !  
    12951396      !                                                      ! ------------------------- ! 
    1296       IF( ssnd(jps_fice)%laction )   CALL cpl_prism_snd( jps_fice, isec, fr_i                  , info ) 
    1297       IF( ssnd(jps_hice)%laction )   CALL cpl_prism_snd( jps_hice, isec, hicif(:,:) * fr_i(:,:), info ) 
    1298       IF( ssnd(jps_hsnw)%laction )   CALL cpl_prism_snd( jps_hsnw, isec, hsnif(:,:) * fr_i(:,:), info ) 
     1397      ! Send ice fraction field  
     1398      SELECT CASE( sn_snd_thick%clcat ) 
     1399         CASE( 'yes' )    
     1400            ztmp3(:,:,1:jpl) =  a_i(:,:,1:jpl) 
     1401         CASE( 'no' ) 
     1402            ztmp3(:,:,1) = fr_i(:,:) 
     1403      CASE default                     ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%clcat' ) 
     1404      END SELECT 
     1405      IF( ssnd(jps_fice)%laction ) CALL cpl_prism_snd( jps_fice, isec, ztmp3, info ) 
     1406 
     1407      ! Send ice and snow thickness field  
     1408      SELECT CASE( sn_snd_thick%cldes) 
     1409      CASE( 'weighted ice and snow' )    
     1410         SELECT CASE( sn_snd_thick%clcat ) 
     1411         CASE( 'yes' )    
     1412            ztmp3(:,:,1:jpl) =  ht_i(:,:,1:jpl) * a_i(:,:,1:jpl) 
     1413            ztmp4(:,:,1:jpl) =  ht_s(:,:,1:jpl) * a_i(:,:,1:jpl) 
     1414         CASE( 'no' ) 
     1415            ztmp3(:,:,:) = 0.0   ;  ztmp4(:,:,:) = 0.0 
     1416            DO jl=1,jpl 
     1417               ztmp3(:,:,1) = ztmp3(:,:,1) + ht_i(:,:,jl) * a_i(:,:,jl) 
     1418               ztmp4(:,:,1) = ztmp4(:,:,1) + ht_s(:,:,jl) * a_i(:,:,jl) 
     1419            ENDDO 
     1420         CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%clcat' ) 
     1421         END SELECT 
     1422      CASE( 'ice and snow'         )    
     1423         ztmp3(:,:,1:jpl) = ht_i(:,:,1:jpl) 
     1424         ztmp4(:,:,1:jpl) = ht_s(:,:,1:jpl) 
     1425      CASE default                     ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%cldes' ) 
     1426      END SELECT 
     1427      IF( ssnd(jps_hice)%laction )   CALL cpl_prism_snd( jps_hice, isec, ztmp3, info ) 
     1428      IF( ssnd(jps_hsnw)%laction )   CALL cpl_prism_snd( jps_hsnw, isec, ztmp4, info ) 
    12991429      ! 
    13001430#if defined key_cpl_carbon_cycle 
     
    13021432      !                                                      !  CO2 flux from PISCES     !  
    13031433      !                                                      ! ------------------------- ! 
    1304       IF( ssnd(jps_co2)%laction )   CALL cpl_prism_snd( jps_co2, isec, oce_co2 , info ) 
     1434      IF( ssnd(jps_co2)%laction )   CALL cpl_prism_snd( jps_co2, isec, RESHAPE ( oce_co2, (/jpi,jpj,1/) ) , info ) 
    13051435      ! 
    13061436#endif 
     1437      !                                                      ! ------------------------- ! 
    13071438      IF( ssnd(jps_ocx1)%laction ) THEN                      !      Surface current      ! 
    13081439         !                                                   ! ------------------------- ! 
     
    13161447         !                                                              i-1  i   i 
    13171448         !                                                               i      i+1 (for I) 
    1318          SELECT CASE( TRIM( cn_snd_crt(1) ) ) 
     1449         SELECT CASE( TRIM( sn_snd_crt%cldes ) ) 
    13191450         CASE( 'oce only'             )      ! C-grid ==> T 
    13201451            DO jj = 2, jpjm1 
     
    13941525            END SELECT 
    13951526         END SELECT 
    1396          CALL lbc_lnk( zotx1, 'T', -1. )   ;   CALL lbc_lnk( zoty1, 'T', -1. ) 
     1527         CALL lbc_lnk( zotx1, ssnd(jps_ocx1)%clgrid, -1. )   ;   CALL lbc_lnk( zoty1, ssnd(jps_ocy1)%clgrid, -1. ) 
    13971528         ! 
    13981529         ! 
    1399          IF( TRIM( cn_snd_crt(3) ) == 'eastward-northward' ) THEN             ! Rotation of the components 
     1530         IF( TRIM( sn_snd_crt%clvor ) == 'eastward-northward' ) THEN             ! Rotation of the components 
    14001531            !                                                                     ! Ocean component 
    14011532            CALL rot_rep( zotx1, zoty1, ssnd(jps_ocx1)%clgrid, 'ij->e', ztmp1 )       ! 1st component  
     
    14121543         ! 
    14131544         ! spherical coordinates to cartesian -> 2 components to 3 components 
    1414          IF( TRIM( cn_snd_crt(2) ) == 'cartesian' ) THEN 
     1545         IF( TRIM( sn_snd_crt%clvref ) == 'cartesian' ) THEN 
    14151546            ztmp1(:,:) = zotx1(:,:)                     ! ocean currents 
    14161547            ztmp2(:,:) = zoty1(:,:) 
     
    14241555         ENDIF 
    14251556         ! 
    1426          IF( ssnd(jps_ocx1)%laction )   CALL cpl_prism_snd( jps_ocx1, isec, zotx1, info )   ! ocean x current 1st grid 
    1427          IF( ssnd(jps_ocy1)%laction )   CALL cpl_prism_snd( jps_ocy1, isec, zoty1, info )   ! ocean y current 1st grid 
    1428          IF( ssnd(jps_ocz1)%laction )   CALL cpl_prism_snd( jps_ocz1, isec, zotz1, info )   ! ocean z current 1st grid 
     1557         IF( ssnd(jps_ocx1)%laction )   CALL cpl_prism_snd( jps_ocx1, isec, RESHAPE ( zotx1, (/jpi,jpj,1/) ), info )   ! ocean x current 1st grid 
     1558         IF( ssnd(jps_ocy1)%laction )   CALL cpl_prism_snd( jps_ocy1, isec, RESHAPE ( zoty1, (/jpi,jpj,1/) ), info )   ! ocean y current 1st grid 
     1559         IF( ssnd(jps_ocz1)%laction )   CALL cpl_prism_snd( jps_ocz1, isec, RESHAPE ( zotz1, (/jpi,jpj,1/) ), info )   ! ocean z current 1st grid 
    14291560         ! 
    1430          IF( ssnd(jps_ivx1)%laction )   CALL cpl_prism_snd( jps_ivx1, isec, zitx1, info )   ! ice   x current 1st grid 
    1431          IF( ssnd(jps_ivy1)%laction )   CALL cpl_prism_snd( jps_ivy1, isec, zity1, info )   ! ice   y current 1st grid 
    1432          IF( ssnd(jps_ivz1)%laction )   CALL cpl_prism_snd( jps_ivz1, isec, zitz1, info )   ! ice   z current 1st grid 
     1561         IF( ssnd(jps_ivx1)%laction )   CALL cpl_prism_snd( jps_ivx1, isec, RESHAPE ( zitx1, (/jpi,jpj,1/) ), info )   ! ice   x current 1st grid 
     1562         IF( ssnd(jps_ivy1)%laction )   CALL cpl_prism_snd( jps_ivy1, isec, RESHAPE ( zity1, (/jpi,jpj,1/) ), info )   ! ice   y current 1st grid 
     1563         IF( ssnd(jps_ivz1)%laction )   CALL cpl_prism_snd( jps_ivz1, isec, RESHAPE ( zitz1, (/jpi,jpj,1/) ), info )   ! ice   z current 1st grid 
    14331564         !  
    14341565      ENDIF 
    14351566      ! 
    1436       IF( wrk_not_released(2, 1,2,3,4,5,6,7,8,9) )   CALL ctl_stop('sbc_cpl_snd: failed to release workspace arrays') 
     1567      IF( wrk_not_released(2, 1,2,3,4,5,6,7,8,9) .OR. wrk_not_released(3, 1,2) )   CALL ctl_stop('sbc_cpl_snd: failed to release workspace arrays') 
    14371568      ! 
    14381569   END SUBROUTINE sbc_cpl_snd 
     
    14591590   END SUBROUTINE sbc_cpl_ice_tau 
    14601591   ! 
    1461    SUBROUTINE sbc_cpl_ice_flx( p_frld  ,                                  & 
    1462       &                        pqns_tot, pqns_ice, pqsr_tot , pqsr_ice,   & 
    1463       &                        pemp_tot, pemp_ice, pdqns_ice, psprecip,   & 
    1464       &                        palbi   , psst    , pist                ) 
    1465       REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   p_frld     ! lead fraction                [0 to 1] 
    1466       REAL(wp), INTENT(  out), DIMENSION(:,:  ) ::   pqns_tot   ! total non solar heat flux    [W/m2] 
    1467       REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   pqns_ice   ! ice   non solar heat flux    [W/m2] 
    1468       REAL(wp), INTENT(  out), DIMENSION(:,:  ) ::   pqsr_tot   ! total     solar heat flux    [W/m2] 
    1469       REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   pqsr_ice   ! ice       solar heat flux    [W/m2] 
    1470       REAL(wp), INTENT(  out), DIMENSION(:,:  ) ::   pemp_tot   ! total     freshwater budget  [Kg/m2/s] 
    1471       REAL(wp), INTENT(  out), DIMENSION(:,:  ) ::   pemp_ice   ! ice solid freshwater budget  [Kg/m2/s] 
    1472       REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   pdqns_ice  ! d(Q non solar)/d(Temperature) over ice 
    1473       REAL(wp), INTENT(  out), DIMENSION(:,:  ) ::   psprecip   ! solid precipitation          [Kg/m2/s] 
     1592   SUBROUTINE sbc_cpl_ice_flx( p_frld , palbi   , psst    , pist  ) 
     1593      REAL(wp), INTENT(in   ), DIMENSION(:,:  ) ::   p_frld     ! lead fraction                [0 to 1] 
    14741594      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   palbi   ! ice albedo 
    14751595      REAL(wp), INTENT(in   ), DIMENSION(:,:  ), OPTIONAL ::   psst    ! sea surface temperature      [Celcius] 
    14761596      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   pist    ! ice surface temperature      [Kelvin] 
    1477       WRITE(*,*) 'sbc_cpl_snd: You should not have seen this print! error?', p_frld(1,1,1), palbi(1,1,1), psst(1,1), pist(1,1,1)  
    1478       ! stupid definition to avoid warning message when compiling... 
    1479       pqns_tot(:,:) = 0. ; pqns_ice(:,:,:) = 0. ; pdqns_ice(:,:,:) = 0. 
    1480       pqsr_tot(:,:) = 0. ; pqsr_ice(:,:,:) = 0.  
    1481       pemp_tot(:,:) = 0. ; pemp_ice(:,:)   = 0. ; psprecip(:,:) = 0. 
     1597      WRITE(*,*) 'sbc_cpl_snd: You should not have seen this print! error?', p_frld(1,1), palbi(1,1,1), psst(1,1), pist(1,1,1)  
    14821598   END SUBROUTINE sbc_cpl_ice_flx 
    14831599    
  • branches/2011/dev_NOC_UKMO_MERGE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_if.F90

    r2715 r3094  
    1616   USE eosbn2          ! equation of state 
    1717   USE sbc_oce         ! surface boundary condition: ocean fields 
     18   USE sbccpl 
    1819   USE fldread         ! read input field 
    1920   USE iom             ! I/O manager library 
     
    9798          
    9899         fr_i(:,:) = tfreez( sss_m ) * tmask(:,:,1)      ! sea surface freezing temperature [Celcius] 
     100#if defined key_coupled  
     101         a_i(:,:,1) = fr_i(:,:)          
     102#endif 
    99103 
    100104         ! Flux and ice fraction computation 
  • branches/2011/dev_NOC_UKMO_MERGE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90

    r2715 r3094  
    202202#if defined key_coupled 
    203203         !                                             ! Ice surface fluxes in coupled mode  
    204          IF( ksbc == 5 )   CALL sbc_cpl_ice_flx( reshape( frld, (/jpi,jpj,1/) ),                 & 
    205             &                                             qns_tot, qns_ice, qsr_tot , qsr_ice,   & 
    206             &                                             emp_tot, emp_ice, dqns_ice, sprecip,   & 
     204         IF( ksbc == 5 )   THEN 
     205            a_i(:,:,1)=fr_i 
     206            CALL sbc_cpl_ice_flx( frld,                                              & 
    207207            !                                optional arguments, used only in 'mixed oce-ice' case 
    208208            &                                             palbi = zalb_ice_cs, psst = sst_m, pist = zsist ) 
     209            sprecip(:,:) = - emp_ice(:,:)   ! Ugly patch, WARNING, in coupled mode, sublimation included in snow (parsub = 0.) 
     210         ENDIF 
    209211#endif 
    210212                           CALL lim_thd_2      ( kt )      ! Ice thermodynamics  
  • branches/2011/dev_NOC_UKMO_MERGE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r2715 r3094  
    1111   !!             -   ! 2010-11  (G. Madec) ice-ocean stress always computed at each ocean time-step 
    1212   !!             -   ! 2010-10  (J. Chanut, C. Bricaud, G. Madec)  add the surface pressure forcing 
     13   !!            3.4  ! 2011-11  (C. Harris) CICE added as an option 
    1314   !!---------------------------------------------------------------------- 
    1415 
     
    3233   USE sbcice_lim       ! surface boundary condition: LIM 3.0 sea-ice model 
    3334   USE sbcice_lim_2     ! surface boundary condition: LIM 2.0 sea-ice model 
     35   USE sbcice_cice      ! surface boundary condition: CICE    sea-ice model 
    3436   USE sbccpl           ! surface boundary condition: coupled florulation 
    3537   USE cpl_oasis3, ONLY:lk_cpl      ! are we in coupled mode? 
     
    3840   USE sbcfwb           ! surface boundary condition: freshwater budget 
    3941   USE closea           ! closed sea 
    40    USE bdy_par          ! unstructured open boundary data variables 
    41    USE bdyice           ! unstructured open boundary data  (bdy_ice_frs routine) 
     42   USE bdy_par          ! for lk_bdy 
     43   USE bdyice_lim2      ! unstructured open boundary data  (bdy_ice_lim_2 routine) 
    4244 
    4345   USE prtctl           ! Print control                    (prt_ctl routine) 
     
    9496        IF( lk_lim2 )   nn_ice      = 2 
    9597        IF( lk_lim3 )   nn_ice      = 3 
     98        IF( lk_cice )   nn_ice      = 4 
    9699      ENDIF 
    97100      IF( cp_cfg == 'gyre' ) THEN            ! GYRE configuration 
     
    144147         &  CALL ctl_warn( 'nn_fsbc is NOT a multiple of the number of time steps in a day' ) 
    145148      ! 
    146       IF( nn_ice == 2 .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. lk_cpl ) )   & 
    147          &   CALL ctl_stop( 'sea-ice model requires a bulk formulation or coupled configuration' ) 
     149      IF( ( nn_ice == 2 .OR. nn_ice ==3 ) .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. lk_cpl ) )   & 
     150         &   CALL ctl_stop( 'LIM sea-ice model requires a bulk formulation or coupled configuration' ) 
     151      IF( nn_ice == 4 .AND. .NOT.( ln_blk_core .OR. lk_cpl ) )   & 
     152         &   CALL ctl_stop( 'CICE sea-ice model requires ln_blk_core or lk_cpl' ) 
     153      IF( nn_ice == 4 .AND. ( .NOT. ( cp_cfg == 'orca' ) .OR. lk_agrif ) )   & 
     154         &   CALL ctl_stop( 'CICE sea-ice model currently only available in a global ORCA configuration without AGRIF' ) 
    148155       
    149156      IF( ln_dm2dc )   nday_qsr = -1   ! initialisation flag 
     
    182189         IF( nsbc ==  5 )   WRITE(numout,*) '              coupled formulation' 
    183190      ENDIF 
     191 
     192      IF( nn_ice == 4 )   CALL cice_sbc_init (nsbc) 
    184193      ! 
    185194   END SUBROUTINE sbc_init 
     
    253262         !                                                       
    254263      CASE(  2 )   ;       CALL sbc_ice_lim_2( kt, nsbc )            ! LIM-2 ice model 
    255          IF( lk_bdy )      CALL bdy_ice_frs  ( kt )                  ! BDY boundary condition 
     264         IF( lk_bdy )      CALL bdy_ice_lim_2( kt )                  ! BDY boundary condition 
    256265         !                                                      
    257266      CASE(  3 )   ;       CALL sbc_ice_lim  ( kt, nsbc )            ! LIM-3 ice model 
     267         ! 
     268      CASE(  4 )   ;       CALL sbc_ice_cice ( kt, nsbc )            ! CICE ice model 
    258269      END SELECT                                               
    259270 
     
    338349            &         tab2d_2=vtau      , clinfo2=' vtau     - : ', mask2=vmask, ovlap=1 ) 
    339350      ENDIF 
     351 
     352      IF( kt == nitend )   CALL sbc_final         ! Close down surface module if necessary 
    340353      ! 
    341354   END SUBROUTINE sbc 
     355 
     356   SUBROUTINE sbc_final 
     357      !!--------------------------------------------------------------------- 
     358      !!                    ***  ROUTINE sbc_final  *** 
     359      !!--------------------------------------------------------------------- 
     360 
     361      !----------------------------------------------------------------- 
     362      ! Finalize CICE (if used) 
     363      !----------------------------------------------------------------- 
     364 
     365      IF( nn_ice == 4 )   CALL cice_sbc_final 
     366      ! 
     367   END SUBROUTINE sbc_final 
    342368 
    343369   !!====================================================================== 
Note: See TracChangeset for help on using the changeset viewer.