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 4990 for trunk/NEMOGCM/NEMO/LIM_SRC_2 – NEMO

Ignore:
Timestamp:
2014-12-15T17:42:49+01:00 (9 years ago)
Author:
timgraham
Message:

Merged branches/2014/dev_MERGE_2014 back onto the trunk as follows:

In the working copy of branch ran:
svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk@HEAD
1 conflict in LIM_SRC_3/limdiahsb.F90
Resolved by keeping the version from dev_MERGE_2014 branch
and commited at r4989

In working copy run:
svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
to switch working copy

Run:
svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2014/dev_MERGE_2014
to merge the branch into the trunk - no conflicts at this stage.

Location:
trunk/NEMOGCM/NEMO/LIM_SRC_2
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/limhdf_2.F90

    r3625 r4990  
    8686      zdiv0(:, 1 ) = 0._wp 
    8787      zdiv0(:,jpj) = 0._wp 
    88       IF( .NOT.lk_vopt_loop ) THEN 
    89          zflu (jpi,:) = 0._wp    
    90          zflv (jpi,:) = 0._wp 
    91          zdiv0(1,  :) = 0._wp 
    92          zdiv0(jpi,:) = 0._wp 
    93       ENDIF 
     88      zflu (jpi,:) = 0._wp    
     89      zflv (jpi,:) = 0._wp 
     90      zdiv0(1,  :) = 0._wp 
     91      zdiv0(jpi,:) = 0._wp 
    9492 
    9593      zconv = 1._wp           !==  horizontal diffusion using a Crant-Nicholson scheme  ==! 
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/limistate_2.F90

    r4624 r4990  
    1414   !!   'key_lim2' :                                  LIM 2.0 sea-ice model 
    1515   !!---------------------------------------------------------------------- 
    16    !!---------------------------------------------------------------------- 
    1716   !!   lim_istate_2      :  Initialisation of diagnostics ice variables 
    1817   !!   lim_istate_init_2 :  initialization of ice state and namelist read 
     
    3433   PUBLIC lim_istate_2      ! routine called by lim_init_2.F90 
    3534 
    36    !!! **  namelist (namiceini) ** 
    37    LOGICAL  ::   ln_limini   !: Ice initialization state 
     35   !                        !! **  namelist (namiceini) ** 
     36   LOGICAL  ::   ln_limini   ! Ice initialization state 
    3837   REAL(wp) ::   ttest       ! threshold water temperature for initial sea ice 
    3938   REAL(wp) ::   hninn       ! initial snow thickness in the north 
     
    5150   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    5251   !!---------------------------------------------------------------------- 
    53  
    5452CONTAINS 
    5553 
     
    7169      IF( .NOT. ln_limini ) THEN   
    7270          
    73          tfu(:,:) = tfreez( tsn(:,:,1,jp_sal) ) * tmask(:,:,1)       ! freezing/melting point of sea water [Celcius] 
     71         tfu(:,:) = eos_fzp( tsn(:,:,1,jp_sal) ) * tmask(:,:,1)       ! freezing/melting point of sea water [Celcius] 
    7472 
    7573         DO jj = 1, jpj 
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/limsbc_2.F90

    r4306 r4990  
    3030   USE sbc_oce          ! surface boundary condition: ocean 
    3131   USE sbccpl 
    32    USE cpl_oasis3, ONLY : lk_cpl 
    3332   USE oce       , ONLY : sshn, sshb, snwice_mass, snwice_mass_b, snwice_fmass  
    3433   USE albedo           ! albedo parameters 
     
    3736   USE wrk_nemo         ! work arrays 
    3837   USE in_out_manager   ! I/O manager 
    39    USE diaar5, ONLY :   lk_diaar5 
    4038   USE iom              ! I/O library 
    4139   USE prtctl           ! Print control 
     
    9795      !!              - emp     : freshwater budget: mass flux  
    9896      !!              - sfx     : freshwater budget: salt flux due to Freezing/Melting 
    99       !!              - utau    : sea surface i-stress (ocean referential) 
    100       !!              - vtau    : sea surface j-stress (ocean referential) 
    10197      !!              - fr_i    : ice fraction 
    10298      !!              - tn_ice  : sea-ice surface temperature 
    103       !!              - alb_ice : sea-ice alberdo (lk_cpl=T) 
     99      !!              - alb_ice : sea-ice albedo (lk_cpl=T) 
    104100      !! 
    105101      !! References : Goosse, H. et al. 1996, Bul. Soc. Roy. Sc. Liege, 65, 87-90. 
     
    183179 
    184180            !   computation the solar flux at ocean surface 
    185 #if defined key_coupled  
    186             zqsr = qsr_tot(ji,jj) + ( fstric(ji,jj) - qsr_ice(ji,jj,1) ) * ( 1.0 - pfrld(ji,jj) ) 
    187 #else 
    188             zqsr = pfrld(ji,jj) * qsr(ji,jj)  + ( 1.  - pfrld(ji,jj) ) * fstric(ji,jj) 
    189 #endif             
     181            IF( lk_cpl ) THEN 
     182               zqsr = qsr_tot(ji,jj) + ( fstric(ji,jj) - qsr_ice(ji,jj,1) ) * ( 1.0 - pfrld(ji,jj) ) 
     183            ELSE 
     184               zqsr = pfrld(ji,jj) * qsr(ji,jj)  + ( 1.  - pfrld(ji,jj) ) * fstric(ji,jj) 
     185            ENDIF 
    190186            !  computation the non solar heat flux at ocean surface 
    191187            zqns    =  - ( 1. - thcm(ji,jj) ) * zqsr                                              &   ! part of the solar energy used in leads 
     
    206202            ! 
    207203            ! mass flux at the ocean-atmosphere interface (open ocean fraction = leads area) 
    208 #if defined key_coupled 
    209204            !                                                  ! coupled mode:  
    210             zemp = + emp_tot(ji,jj)                            &     ! net mass flux over the grid cell (ice+ocean area) 
    211                &   - emp_ice(ji,jj) * ( 1. - pfrld(ji,jj) )          ! minus the mass flux intercepted by sea-ice 
    212 #else 
    213             !                                                  ! forced  mode:  
    214             zemp = + emp(ji,jj)     *         frld(ji,jj)      &     ! mass flux over open ocean fraction  
    215                &   - tprecip(ji,jj) * ( 1. -  frld(ji,jj) )    &     ! liquid precip. over ice reaches directly the ocean 
    216                &   + sprecip(ji,jj) * ( 1. - pfrld(ji,jj) )          ! snow is intercepted by sea-ice (previous frld) 
    217 #endif             
     205            IF( lk_cpl ) THEN 
     206               zemp = + emp_tot(ji,jj)                            &     ! net mass flux over the grid cell (ice+ocean area) 
     207                  &   - emp_ice(ji,jj) * ( 1. - pfrld(ji,jj) )          ! minus the mass flux intercepted by sea-ice 
     208            ELSE 
     209               !                                                  ! forced  mode:  
     210               zemp = + emp(ji,jj)     *         frld(ji,jj)      &     ! mass flux over open ocean fraction  
     211                  &   - tprecip(ji,jj) * ( 1. -  frld(ji,jj) )    &     ! liquid precip. over ice reaches directly the ocean 
     212                  &   + sprecip(ji,jj) * ( 1. - pfrld(ji,jj) )          ! snow is intercepted by sea-ice (previous frld) 
     213            ENDIF 
    218214            ! 
    219215            ! mass flux at the ocean/ice interface (sea ice fraction) 
     
    245241      ENDIF 
    246242 
    247       CALL iom_put( 'hflx_ice_cea', - fdtcn(:,:) )       
    248       CALL iom_put( 'qns_io_cea', qns(:,:) - zqnsoce(:,:) * pfrld(:,:) )       
    249       CALL iom_put( 'qsr_io_cea', fstric(:,:) * (1.e0 - pfrld(:,:)) ) 
    250  
    251       IF( lk_diaar5 ) THEN       ! AR5 diagnostics 
    252          CALL iom_put( 'isnwmlt_cea'  ,                 rdm_snw(:,:) * r1_rdtice ) 
    253          CALL iom_put( 'fsal_virt_cea',   soce_0(:,:) * rdm_ice(:,:) * r1_rdtice ) 
    254          CALL iom_put( 'fsal_real_cea', - sice_0(:,:) * rdm_ice(:,:) * r1_rdtice ) 
    255       ENDIF 
     243      IF( iom_use('hflx_ice_cea' ) )   CALL iom_put( 'hflx_ice_cea', - fdtcn(:,:) )       
     244      IF( iom_use('qns_io_cea'   ) )   CALL iom_put( 'qns_io_cea', qns(:,:) - zqnsoce(:,:) * pfrld(:,:) )       
     245      IF( iom_use('qsr_io_cea'   ) )   CALL iom_put( 'qsr_io_cea', fstric(:,:) * (1.e0 - pfrld(:,:)) ) 
     246 
     247      IF( iom_use('isnwmlt_cea'  ) )   CALL iom_put( 'isnwmlt_cea'  ,                 rdm_snw(:,:) * r1_rdtice ) 
     248      IF( iom_use('fsal_virt_cea') )   CALL iom_put( 'fsal_virt_cea',   soce_0(:,:) * rdm_ice(:,:) * r1_rdtice ) 
     249      IF( iom_use('fsal_real_cea') )   CALL iom_put( 'fsal_real_cea', - sice_0(:,:) * rdm_ice(:,:) * r1_rdtice ) 
    256250 
    257251      !-----------------------------------------------! 
     
    259253      !-----------------------------------------------! 
    260254 
    261 #if defined key_coupled 
    262       tn_ice(:,:,1) = sist(:,:)          ! sea-ice surface temperature        
    263       ht_i(:,:,1) = hicif(:,:) 
    264       ht_s(:,:,1) = hsnif(:,:) 
    265       a_i(:,:,1) = fr_i(:,:) 
    266       !                                  ! Computation of snow/ice and ocean albedo 
    267       CALL albedo_ice( tn_ice, ht_i, ht_s, zalbp, zalb ) 
    268       alb_ice(:,:,1) =  0.5 * ( zalbp(:,:,1) + zalb (:,:,1) )   ! Ice albedo (mean clear and overcast skys) 
    269       CALL iom_put( "icealb_cea", alb_ice(:,:,1) * fr_i(:,:) )  ! ice albedo 
    270 #endif 
     255      IF( lk_cpl) THEN 
     256         tn_ice(:,:,1) = sist(:,:)          ! sea-ice surface temperature        
     257         ht_i(:,:,1) = hicif(:,:) 
     258         ht_s(:,:,1) = hsnif(:,:) 
     259         a_i(:,:,1) = fr_i(:,:) 
     260         !                                  ! Computation of snow/ice and ocean albedo 
     261         CALL albedo_ice( tn_ice, ht_i, ht_s, zalbp, zalb ) 
     262         alb_ice(:,:,1) =  0.5 * ( zalbp(:,:,1) + zalb (:,:,1) )   ! Ice albedo (mean clear and overcast skys) 
     263         IF( iom_use('icealb_cea' ) )   CALL iom_put( 'icealb_cea', alb_ice(:,:,1) * fr_i(:,:) )  ! ice albedo 
     264      ENDIF 
    271265 
    272266      IF(ln_ctl) THEN            ! control print 
    273267         CALL prt_ctl(tab2d_1=qsr   , clinfo1=' lim_sbc: qsr    : ', tab2d_2=qns   , clinfo2=' qns     : ') 
    274268         CALL prt_ctl(tab2d_1=emp   , clinfo1=' lim_sbc: emp    : ', tab2d_2=sfx   , clinfo2=' sfx     : ') 
    275          CALL prt_ctl(tab2d_1=utau  , clinfo1=' lim_sbc: utau   : ', mask1=umask,   & 
    276             &         tab2d_2=vtau  , clinfo2=' vtau    : '        , mask2=vmask ) 
    277269         CALL prt_ctl(tab2d_1=fr_i  , clinfo1=' lim_sbc: fr_i   : ', tab2d_2=tn_ice(:,:,1), clinfo2=' tn_ice  : ') 
    278270      ENDIF  
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/limthd_2.F90

    r4696 r4990  
    3333   USE limtab_2 
    3434   USE prtctl           ! Print control 
    35    USE cpl_oasis3, ONLY :   lk_cpl 
    36    USE diaar5    , ONLY :   lk_diaar5 
    3735   USE lib_fortran      ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
    3836    
     
    219217                         
    220218            !  partial computation of the lead energy budget (qldif) 
    221 #if defined key_coupled  
    222             qldif(ji,jj)   = tms(ji,jj) * rdt_ice                                                  & 
    223                &    * (   ( qsr_tot(ji,jj) - qsr_ice(ji,jj,1) * zfricp ) * ( 1.0 - thcm(ji,jj) )   & 
    224                &        + ( qns_tot(ji,jj) - qns_ice(ji,jj,1) * zfricp )                           & 
    225                &        + frld(ji,jj) * ( fdtcn(ji,jj) + ( 1.0 - zindb ) * fsbbq(ji,jj) )   ) 
    226 #else 
    227             qldif(ji,jj)   = tms(ji,jj) * rdt_ice * frld(ji,jj)                    & 
    228                &                        * (  qsr(ji,jj) * ( 1.0 - thcm(ji,jj) )    & 
    229                &                           + qns(ji,jj)  +  fdtcn(ji,jj)           & 
    230                &                           + ( 1.0 - zindb ) * fsbbq(ji,jj)      ) 
    231 #endif 
     219            IF( lk_cpl ) THEN  
     220               qldif(ji,jj)   = tms(ji,jj) * rdt_ice                                                  & 
     221                  &    * (   ( qsr_tot(ji,jj) - qsr_ice(ji,jj,1) * zfricp ) * ( 1.0 - thcm(ji,jj) )   & 
     222                  &        + ( qns_tot(ji,jj) - qns_ice(ji,jj,1) * zfricp )                           & 
     223                  &        + frld(ji,jj) * ( fdtcn(ji,jj) + ( 1.0 - zindb ) * fsbbq(ji,jj) )   ) 
     224            ELSE 
     225               qldif(ji,jj)   = tms(ji,jj) * rdt_ice * frld(ji,jj)                    & 
     226                  &                        * (  qsr(ji,jj) * ( 1.0 - thcm(ji,jj) )    & 
     227                  &                           + qns(ji,jj)  +  fdtcn(ji,jj)           & 
     228                  &                           + ( 1.0 - zindb ) * fsbbq(ji,jj)      ) 
     229            ENDIF 
    232230            !  parlat : percentage of energy used for lateral ablation (0.0)  
    233231            zfntlat        = 1.0 - MAX( rzero , SIGN( rone ,  - qldif(ji,jj) ) ) 
     
    440438      !-------------------------------------------------------------------------------- 
    441439      ztmp(:,:) = 1. - pfrld(:,:)                                ! fraction of ice after the dynamic, before the thermodynamic 
    442       CALL iom_put( 'ist_cea', (sist(:,:) - rt0) * ztmp(:,:) )   ! Ice surface temperature                [Celius] 
    443       CALL iom_put( 'qsr_ai_cea', qsr_ice(:,:,1) * ztmp(:,:) )   ! Solar flux over the ice                [W/m2] 
    444       CALL iom_put( 'qns_ai_cea', qns_ice(:,:,1) * ztmp(:,:) )   ! Non-solar flux over the ice            [W/m2] 
    445       IF( .NOT. lk_cpl )   CALL iom_put( 'qla_ai_cea', qla_ice(:,:,1) * ztmp(:,:) )     ! Latent flux over the ice  [W/m2] 
     440      IF( iom_use('ist_cea'    ) )   CALL iom_put( 'ist_cea', (sist(:,:) - rt0) * ztmp(:,:) )   ! Ice surface temperature   [Celius] 
     441      IF( iom_use('qsr_ai_cea' ) )   CALL iom_put( 'qsr_ai_cea', qsr_ice(:,:,1) * ztmp(:,:) )   ! Solar flux over the ice     [W/m2] 
     442      IF( iom_use('qns_ai_cea' ) )   CALL iom_put( 'qns_ai_cea', qns_ice(:,:,1) * ztmp(:,:) )   ! Non-solar flux over the ice [W/m2] 
     443      IF( iom_use('qla_ai_cea' ) .AND. .NOT. lk_cpl ) & 
     444         &                           CALL iom_put( 'qla_ai_cea', qla_ice(:,:,1) * ztmp(:,:) )   ! Latent flux over the ice [W/m2] 
    446445      ! 
    447       CALL iom_put( 'snowthic_cea', hsnif  (:,:) * fr_i(:,:) )   ! Snow thickness             [m] 
    448       CALL iom_put( 'icethic_cea' , hicif  (:,:) * fr_i(:,:) )   ! Ice thickness              [m] 
     446      IF( iom_use('snowthic_cea'))   CALL iom_put( 'snowthic_cea', hsnif  (:,:) * fr_i(:,:) )   ! Snow thickness           [m] 
     447      IF( iom_use('icethic_cea' ))   CALL iom_put( 'icethic_cea' , hicif  (:,:) * fr_i(:,:) )   ! Ice thickness            [m] 
    449448      zztmp = 1.0 / rdt_ice 
    450       CALL iom_put( 'iceprod_cea' , hicifp (:,:) * zztmp     )   ! Ice produced               [m/s] 
    451       IF( lk_diaar5 ) THEN 
    452          CALL iom_put( 'snowmel_cea' , rdm_snw(:,:) * zztmp     )   ! Snow melt                  [kg/m2/s] 
    453          zztmp = rhoic / rdt_ice 
    454          CALL iom_put( 'sntoice_cea' , zdvonif(:,:) * zztmp     )   ! Snow to Ice transformation [kg/m2/s] 
    455          CALL iom_put( 'ticemel_cea' , zdvosif(:,:) * zztmp     )   ! Melt at Sea Ice top        [kg/m2/s] 
    456          CALL iom_put( 'bicemel_cea' , zdvomif(:,:) * zztmp     )   ! Melt at Sea Ice bottom     [kg/m2/s] 
     449      IF( iom_use('iceprod_cea') )   CALL iom_put( 'iceprod_cea' , hicifp (:,:) * zztmp     )   ! Ice produced             [m/s] 
     450      IF( iom_use('iiceconc'   ) )   CALL iom_put( 'iiceconc'    , fr_i(:,:)                )   ! Ice concentration        [-] 
     451      IF( iom_use('snowmel_cea') )   CALL iom_put( 'snowmel_cea' , rdm_snw(:,:) * zztmp     )   ! Snow melt                [kg/m2/s] 
     452      zztmp = rhoic / rdt_ice 
     453      IF( iom_use('sntoice_cea') )   CALL iom_put( 'sntoice_cea' , zdvonif(:,:) * zztmp     ) ! Snow to Ice transformation [kg/m2/s] 
     454      IF( iom_use('ticemel_cea') )   CALL iom_put( 'ticemel_cea' , zdvosif(:,:) * zztmp     )   ! Melt at Sea Ice top      [kg/m2/s] 
     455      IF( iom_use('bicemel_cea') )   CALL iom_put( 'bicemel_cea' , zdvomif(:,:) * zztmp     )   ! Melt at Sea Ice bottom   [kg/m2/s] 
     456      IF( iom_use('licepro_cea') ) THEN 
    457457         zlicegr(:,:) = MAX( 0.e0, rdm_ice(:,:)-zlicegr(:,:) ) 
    458          CALL iom_put( 'licepro_cea' , zlicegr(:,:) * zztmp     )   ! Lateral sea ice growth     [kg/m2/s] 
     458                                     CALL iom_put( 'licepro_cea' , zlicegr(:,:) * zztmp     )   ! Lateral sea ice growth   [kg/m2/s] 
    459459      ENDIF 
    460460      ! 
    461461      ! Compute the Eastward & Northward sea-ice transport 
    462       zztmp = 0.25 * rhoic 
    463       DO jj = 1, jpjm1  
    464          DO ji = 1, jpim1   ! NO vector opt. 
    465             ! Ice velocities, volume & transport at U & V-points 
    466             zuice_m = u_ice(ji+1,jj+1) + u_ice(ji+1,jj ) 
    467             zvice_m = v_ice(ji+1,jj+1) + v_ice(ji ,jj+1) 
    468             zhice_u = hicif(ji,jj)*e2t(ji,jj)*fr_i(ji,jj) + hicif(ji+1,jj  )*e2t(ji+1,jj  )*fr_i(ji+1,jj  ) 
    469             zhice_v = hicif(ji,jj)*e1t(ji,jj)*fr_i(ji,jj) + hicif(ji  ,jj+1)*e1t(ji  ,jj+1)*fr_i(ji  ,jj+1) 
    470             zu_imasstr(ji,jj) = zztmp * zhice_u * zuice_m  
    471             zv_imasstr(ji,jj) = zztmp * zhice_v * zvice_m  
    472          END DO 
    473       END DO 
    474       CALL lbc_lnk( zu_imasstr, 'U', -1. )   ;   CALL lbc_lnk( zv_imasstr, 'V', -1. ) 
    475       CALL iom_put( 'u_imasstr',  zu_imasstr(:,:) )   ! Ice transport along i-axis at U-point [kg/s]  
    476       CALL iom_put( 'v_imasstr',  zv_imasstr(:,:) )   ! Ice transport along j-axis at V-point [kg/s]  
     462      IF( iom_use('u_imasstr') ) THEN 
     463         zztmp = 0.25 * rhoic 
     464         DO jj = 1, jpjm1  
     465            DO ji = 1, jpim1   ! NO vector opt. 
     466               ! Ice velocities, volume & transport at U-points 
     467               zuice_m = u_ice(ji+1,jj+1) + u_ice(ji+1,jj ) 
     468               zhice_u = hicif(ji,jj)*e2t(ji,jj)*fr_i(ji,jj) + hicif(ji+1,jj  )*e2t(ji+1,jj  )*fr_i(ji+1,jj  ) 
     469               zu_imasstr(ji,jj) = zztmp * zhice_u * zuice_m  
     470            END DO 
     471         END DO 
     472         CALL lbc_lnk( zu_imasstr, 'U', -1. ) 
     473         CALL iom_put( 'u_imasstr',  zu_imasstr(:,:) )   ! Ice transport along i-axis at U-point [kg/s]  
     474      ENDIF 
     475      IF( iom_use('v_imasstr') ) THEN 
     476         zztmp = 0.25 * rhoic 
     477         DO jj = 1, jpjm1  
     478            DO ji = 1, jpim1   ! NO vector opt. 
     479               ! Ice velocities, volume & transport at V-points 
     480               zvice_m = v_ice(ji+1,jj+1) + v_ice(ji ,jj+1) 
     481               zhice_v = hicif(ji,jj)*e1t(ji,jj)*fr_i(ji,jj) + hicif(ji  ,jj+1)*e1t(ji  ,jj+1)*fr_i(ji  ,jj+1) 
     482               zv_imasstr(ji,jj) = zztmp * zhice_v * zvice_m  
     483            END DO 
     484         END DO 
     485         CALL lbc_lnk( zv_imasstr, 'V', -1. ) 
     486         CALL iom_put( 'v_imasstr',  zv_imasstr(:,:) )   ! Ice transport along j-axis at V-point [kg/s] 
     487      ENDIF 
    477488 
    478489      !! Fram Strait sea-ice transport (sea-ice + snow)  (in ORCA2 = 5 points) 
    479       IF( cp_cfg == "orca" .AND. jp_cfg == 2 ) THEN    ! ORCA R2 configuration 
     490      IF( iom_use('fram_trans') .and. cp_cfg == "orca" .AND. jp_cfg == 2 ) THEN    ! ORCA R2 configuration 
    480491         DO jj = mj0(137), mj1(137) ! B grid 
    481492            IF( mj0(jj-1) >= nldj ) THEN 
     
    491502      ENDIF 
    492503 
     504      IF( iom_use('ice_pres') .OR. iom_use('ist_ipa') .OR. iom_use('uice_ipa') .OR. iom_use('vice_ipa') ) THEN 
    493505!! ce     ztmp(:,:) = 1. - AINT( frld(:,:), wp )                        ! return 1 as soon as there is ice 
    494506!! ce     A big warning because the model crashes on IDRIS/IBM SP6 with xlf 13.1.0.3, see ticket #761 
    495 !! ce     We Unroll the loop and everything works fine  
    496       DO jj = 1, jpj 
    497          DO ji = 1, jpi 
    498             ztmp(ji,jj) = 1. - AINT( frld(ji,jj), wp )                ! return 1 as soon as there is ice 
    499          END DO 
    500       END DO 
    501       ! 
    502       CALL iom_put( 'ice_pres'  , ztmp                            )   ! Ice presence                          [-] 
    503       CALL iom_put( 'ist_ipa'   , ( sist(:,:) - rt0 ) * ztmp(:,:) )   ! Ice surface temperature               [Celius] 
    504       CALL iom_put( 'uice_ipa'  ,  u_ice(:,:)         * ztmp(:,:) )   ! Ice velocity along i-axis at I-point  [m/s]  
    505       CALL iom_put( 'vice_ipa'  ,  v_ice(:,:)         * ztmp(:,:) )   ! Ice velocity along j-axis at I-point  [m/s] 
     507!! ce     We Unroll the loop and everything works fine       
     508         DO jj = 1, jpj 
     509            DO ji = 1, jpi 
     510               ztmp(ji,jj) = 1. - AINT( frld(ji,jj), wp )                ! return 1 as soon as there is ice 
     511            END DO 
     512         END DO 
     513         ! 
     514         IF( iom_use('ice_pres') ) CALL iom_put( 'ice_pres', ztmp                            )   ! Ice presence                 [-] 
     515         IF( iom_use('ist_ipa' ) ) CALL iom_put( 'ist_ipa' , ( sist(:,:) - rt0 ) * ztmp(:,:) )   ! Ice surface temperature [Celius] 
     516         IF( iom_use('uice_ipa') ) CALL iom_put( 'uice_ipa', u_ice(:,:) * ztmp(:,:) ) ! Ice velocity along i-axis at I-point  [m/s]  
     517         IF( iom_use('vice_ipa') ) CALL iom_put( 'vice_ipa', v_ice(:,:) * ztmp(:,:) ) ! Ice velocity along j-axis at I-point  [m/s] 
     518      ENDIF 
    506519 
    507520      IF(ln_ctl) THEN 
  • trunk/NEMOGCM/NEMO/LIM_SRC_2/limthd_zdf_2.F90

    r4306 r4990  
    1818   USE ice_2 
    1919   USE limistate_2 
    20    USE cpl_oasis3, ONLY : lk_cpl 
     20   USE sbc_oce, ONLY : lk_cpl 
    2121   USE in_out_manager 
    2222   USE lib_mpp          ! MPP library 
Note: See TracChangeset for help on using the changeset viewer.