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 4765 – NEMO

Changeset 4765


Ignore:
Timestamp:
2014-09-16T14:55:11+02:00 (10 years ago)
Author:
rblod
Message:

Compilation issue, see ticket #1379

Location:
trunk/NEMOGCM/NEMO
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/ice.F90

    r4688 r4765  
    522522      ! * Ice diagnostics 
    523523      ii = ii + 1 
    524       ALLOCATE( dv_dt_thd(jpi,jpj,jpl) ,     & 
    525          &      izero    (jpi,jpj,jpl)  , diag_trp_vi(jpi,jpj) , diag_trp_vs(jpi,jpj), diag_trp_ei(jpi,jpj), diag_trp_es(jpi,jpj),     &  
    526          &      diag_heat_dhc(jpi,jpj) ,  STAT=ierr(ii) ) 
     524      ALLOCATE( dv_dt_thd(jpi,jpj,jpl), izero (jpi,jpj,jpl),    & 
     525         &      diag_trp_vi(jpi,jpj), diag_trp_vs  (jpi,jpj), diag_trp_ei(jpi,jpj),   &  
     526         &      diag_trp_es(jpi,jpj), diag_heat_dhc(jpi,jpj),  STAT=ierr(ii) ) 
    527527 
    528528      ice_alloc = MAXVAL( ierr(:) ) 
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/limcons.F90

    r4688 r4765  
    175175         zei_b  = glob_sum( SUM(   e_i(:,:,1:nlay_i,:), dim=3 ) + SUM( e_s(:,:,1:nlay_s,:), dim=3 ) ) 
    176176         zfw_b  = glob_sum( - ( wfx_bog(:,:) + wfx_bom(:,:) + wfx_sum(:,:) + wfx_sni(:,:) + wfx_opw(:,:) +  & 
    177             &                   wfx_res(:,:) + wfx_dyn(:,:) + wfx_snw(:,:) + wfx_sub(:,:) + wfx_spr(:,:) ) * area(:,:) * tms(:,:) ) 
     177            &                   wfx_res(:,:) + wfx_dyn(:,:) + wfx_snw(:,:) + wfx_sub(:,:) + wfx_spr(:,:)    & 
     178            &             ) * area(:,:) * tms(:,:) ) 
    178179         zfs_b  = glob_sum(   ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) +  & 
    179             &                   sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) ) * area(:,:) * tms(:,:) ) 
     180            &                   sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:)                                  & 
     181            &                 ) * area(:,:) * tms(:,:) ) 
    180182         zft_b  = glob_sum(   ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:)  &  
    181             &                 - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:) ) * area(:,:) / unit_fac * tms(:,:) ) 
     183            &                 - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:)   & 
     184            &                  ) * area(:,:) / unit_fac * tms(:,:) ) 
    182185 
    183186      ELSEIF( icount == 1 ) THEN 
    184187 
    185188         zfs  = glob_sum(   ( sfx_bri(:,:) + sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) +  & 
    186             &                 sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) ) * area(:,:) * tms(:,:) ) - zfs_b 
     189            &                 sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:)                                  &  
     190            &                ) * area(:,:) * tms(:,:) ) - zfs_b 
    187191         zfw  = glob_sum( - ( wfx_bog(:,:) + wfx_bom(:,:) + wfx_sum(:,:) + wfx_sni(:,:) + wfx_opw(:,:) +  & 
    188             &                 wfx_res(:,:) + wfx_dyn(:,:) + wfx_snw(:,:) + wfx_sub(:,:) + wfx_spr(:,:) ) * area(:,:) * tms(:,:) ) - zfw_b 
     192            &                 wfx_res(:,:) + wfx_dyn(:,:) + wfx_snw(:,:) + wfx_sub(:,:) + wfx_spr(:,:)    & 
     193            &                ) * area(:,:) * tms(:,:) ) - zfw_b 
    189194         zft  = glob_sum(   ( hfx_sum(:,:) + hfx_bom(:,:) + hfx_bog(:,:) + hfx_dif(:,:) + hfx_opw(:,:) + hfx_snw(:,:)  &  
    190             &               - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:) ) * area(:,:) / unit_fac * tms(:,:) ) - zft_b 
     195            &               - hfx_thd(:,:) - hfx_dyn(:,:) - hfx_res(:,:) - hfx_sub(:,:) - hfx_spr(:,:)   & 
     196            &                ) * area(:,:) / unit_fac * tms(:,:) ) - zft_b 
    191197  
    192198         zvi  = ( glob_sum( SUM(   v_i(:,:,:)*rhoic + v_s(:,:,:)*rhosn, dim=3 ) * area(:,:) * tms(:,:) ) - zvi_b ) * r1_rdtice - zfw  
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/limdiahsb.F90

    r4688 r4765  
    5959      !! 
    6060      REAL(dp)   ::   zbg_ivo, zbg_svo, zbg_are, zbg_sal ,zbg_tem ,zbg_ihc ,zbg_shc 
    61       REAL(dp)   ::   zbg_sfx, zbg_sfx_bri, zbg_sfx_bog, zbg_sfx_bom, zbg_sfx_sum, zbg_sfx_sni, zbg_sfx_opw, zbg_sfx_res, zbg_sfx_dyn  
     61      REAL(dp)   ::   zbg_sfx, zbg_sfx_bri, zbg_sfx_bog, zbg_sfx_bom, zbg_sfx_sum, zbg_sfx_sni,   & 
     62      &               zbg_sfx_opw, zbg_sfx_res, zbg_sfx_dyn  
    6263      REAL(dp)   ::   zbg_vfx, zbg_vfx_bog, zbg_vfx_opw, zbg_vfx_sni, zbg_vfx_dyn 
    6364      REAL(dp)   ::   zbg_vfx_bom, zbg_vfx_sum, zbg_vfx_res, zbg_vfx_spr, zbg_vfx_snw, zbg_vfx_sub   
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/limistate.F90

    r4688 r4765  
    136136      DO jj = 1, jpj                                        
    137137         DO ji = 1, jpi 
    138             IF( ( tsn(ji,jj,1,jp_tem)  - ( t_bo(ji,jj) - rt0 ) ) * tms(ji,jj) >= thres_sst ) THEN  ; zswitch(ji,jj) = 0._wp * tms(ji,jj)    ! no ice 
    139             ELSE                                                                                   ; zswitch(ji,jj) = 1._wp * tms(ji,jj)    !    ice 
     138            IF( ( tsn(ji,jj,1,jp_tem)  - ( t_bo(ji,jj) - rt0 ) ) * tms(ji,jj) >= thres_sst ) THEN  
     139               zswitch(ji,jj) = 0._wp * tms(ji,jj)    ! no ice 
     140            ELSE                                                                                    
     141               zswitch(ji,jj) = 1._wp * tms(ji,jj)    !    ice 
    140142            ENDIF 
    141143         END DO 
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r4688 r4765  
    182182 
    183183            ! mass flux from ice/ocean 
    184             wfx_ice(ji,jj) = wfx_bog(ji,jj) + wfx_bom(ji,jj) + wfx_sum(ji,jj) + wfx_sni(ji,jj) + wfx_opw(ji,jj) + wfx_dyn(ji,jj) + wfx_res(ji,jj) 
     184            wfx_ice(ji,jj) = wfx_bog(ji,jj) + wfx_bom(ji,jj) + wfx_sum(ji,jj) + wfx_sni(ji,jj)   & 
     185                           + wfx_opw(ji,jj) + wfx_dyn(ji,jj) + wfx_res(ji,jj) 
    185186 
    186187            ! mass flux at the ocean/ice interface 
     
    194195      !      salt flux at the ocean surface      ! 
    195196      !------------------------------------------! 
    196       sfx(:,:) = sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) + sfx_opw(:,:) + sfx_res(:,:) + sfx_dyn(:,:) + sfx_bri(:,:) 
     197      sfx(:,:) = sfx_bog(:,:) + sfx_bom(:,:) + sfx_sum(:,:) + sfx_sni(:,:) + sfx_opw(:,:)   & 
     198         &     + sfx_res(:,:) + sfx_dyn(:,:) + sfx_bri(:,:) 
    197199 
    198200      !-------------------------------------------------------------! 
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/limthd.F90

    r4688 r4765  
    154154               &                           + qns(ji,jj) )                        &   ! non solar heat 
    155155               ! latent heat of precip (note that precip is included in qns but not in qns_ice) 
    156                &    + ( pfrld(ji,jj)**betas - pfrld(ji,jj) ) * sprecip(ji,jj) * ( cpic * ( MIN( tatm_ice(ji,jj), rt0_snow ) - rtt ) - lfus )  & 
    157                &    + ( 1._wp - pfrld(ji,jj) ) * ( tprecip(ji,jj) - sprecip(ji,jj) ) * rcp * ( tatm_ice(ji,jj) - rtt ) ) 
     156               &    + ( pfrld(ji,jj)**betas - pfrld(ji,jj) ) * sprecip(ji,jj)         & 
     157               &    * ( cpic * ( MIN( tatm_ice(ji,jj), rt0_snow ) - rtt ) - lfus )    & 
     158               &    + ( 1._wp - pfrld(ji,jj) ) * ( tprecip(ji,jj) - sprecip(ji,jj) )  & 
     159               &    * rcp * ( tatm_ice(ji,jj) - rtt ) ) 
    158160 
    159161            !-- Energy needed to bring ocean surface layer until its freezing (<0, J.m-2) --- ! 
     
    196198            !     Second step in limthd_dh      :  heat remaining if total melt (zq_rema)  
    197199            !     Third  step in limsbc         :  heat from ice-ocean mass exchange (zf_mass) + solar 
    198             hfx_out(ji,jj) = hfx_out(ji,jj)                                                                                                        &  
     200            hfx_out(ji,jj) = hfx_out(ji,jj)                                                                                   &  
    199201               ! Non solar heat flux received by the ocean 
    200                &    +        pfrld(ji,jj) * qns(ji,jj)                                                                                             & 
     202               &    +        pfrld(ji,jj) * qns(ji,jj)                                                                        & 
    201203               ! latent heat of precip (note that precip is included in qns but not in qns_ice) 
    202                &    +      ( pfrld(ji,jj)**betas - pfrld(ji,jj) ) * sprecip(ji,jj) * ( cpic * ( MIN( tatm_ice(ji,jj), rt0_snow ) - rtt ) - lfus )  & 
    203                &    +      ( 1._wp - pfrld(ji,jj) ) * ( tprecip(ji,jj) - sprecip(ji,jj) ) * rcp * ( tatm_ice(ji,jj) - rtt )                        & 
     204               &    +      ( pfrld(ji,jj)**betas - pfrld(ji,jj) ) * sprecip(ji,jj)                                            & 
     205               &    * ( cpic * ( MIN( tatm_ice(ji,jj), rt0_snow ) - rtt ) - lfus )                                            & 
     206               &    +      ( 1._wp - pfrld(ji,jj) ) * ( tprecip(ji,jj) - sprecip(ji,jj) ) * rcp * ( tatm_ice(ji,jj) - rtt )   & 
    204207               ! heat flux taken from the ocean where there is open water ice formation 
    205                &    -      qlead(ji,jj) * r1_rdtice                                                                                                & 
     208               &    -      qlead(ji,jj) * r1_rdtice                                                                           & 
    206209               ! heat flux taken from the ocean during bottom growth/melt (fhld should be 0 while bott growth) 
    207                &    -      at_i(ji,jj) * fhtur(ji,jj)                                                                                              & 
     210               &    -      at_i(ji,jj) * fhtur(ji,jj)                                                                         & 
    208211               &    -      at_i(ji,jj) *  fhld(ji,jj) 
    209212 
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/limthd_dif.F90

    r4688 r4765  
    333333            DO layer = 1, nlay_i-1 
    334334               DO ji = kideb , kiut 
    335                   ztcond_i(ji,layer) = rcdic + 0.090_wp * ( s_i_b(ji,layer) + s_i_b(ji,layer+1) )   & 
    336                      &                                  / MIN(-2.0_wp * epsi10, t_i_b(ji,layer)+t_i_b(ji,layer+1) - 2.0_wp * rtt)   & 
    337                      &                       - 0.0055_wp* ( t_i_b(ji,layer) + t_i_b(ji,layer+1) - 2.0*rtt )   
     335                  ztcond_i(ji,layer) = rcdic +                                                                     &  
     336                     &                 0.090_wp * ( s_i_b(ji,layer) + s_i_b(ji,layer+1) )                          & 
     337                     &                 / MIN(-2.0_wp * epsi10, t_i_b(ji,layer)+t_i_b(ji,layer+1) - 2.0_wp * rtt)   & 
     338                     &               - 0.0055_wp* ( t_i_b(ji,layer) + t_i_b(ji,layer+1) - 2.0*rtt )   
    338339                  ztcond_i(ji,layer) = MAX( ztcond_i(ji,layer), zkimin ) 
    339340               END DO 
     
    728729      DO ji = kideb, kiut 
    729730         IF( t_su_b(ji) < rtt ) THEN  ! case T_su < 0degC 
    730             hfx_dif_1d(ji) = hfx_dif_1d(ji) + ( qns_ice_1d(ji) + qsr_ice_1d(ji) - zradtr_i(ji,nlay_i) - fc_bo_i(ji) ) * a_i_b(ji) 
     731            hfx_dif_1d(ji) = hfx_dif_1d(ji)  +   & 
     732               &            ( qns_ice_1d(ji) + qsr_ice_1d(ji) - zradtr_i(ji,nlay_i) - fc_bo_i(ji) ) * a_i_b(ji) 
    731733         ELSE                         ! case T_su = 0degC 
    732             hfx_dif_1d(ji) = hfx_dif_1d(ji) + ( fc_su(ji) + i0(ji) * qsr_ice_1d(ji) - zradtr_i(ji,nlay_i) - fc_bo_i(ji) ) * a_i_b(ji) 
     734            hfx_dif_1d(ji) = hfx_dif_1d(ji) +    & 
     735               &             ( fc_su(ji) + i0(ji) * qsr_ice_1d(ji) - zradtr_i(ji,nlay_i) - fc_bo_i(ji) ) * a_i_b(ji) 
    733736         ENDIF 
    734737      END DO 
     
    755758      CALL wrk_dealloc( jpij, ztfs, ztsuold, ztsuoldit, zh_i, zh_s, zfsw ) 
    756759      CALL wrk_dealloc( jpij, zf, dzf, zerrit, zdifcase, zftrice, zihic, zhsu ) 
    757       CALL wrk_dealloc( jpij, nlay_i+1, ztcond_i, zradtr_i, zradab_i, zkappa_i, ztiold, zeta_i, ztitemp, z_i, zspeche_i, kjstart = 0 ) 
     760      CALL wrk_dealloc( jpij, nlay_i+1, ztcond_i, zradtr_i, zradab_i, zkappa_i,   & 
     761         &              ztiold, zeta_i, ztitemp, z_i, zspeche_i, kjstart = 0 ) 
    758762      CALL wrk_dealloc( jpij, nlay_s+1,           zradtr_s, zradab_s, zkappa_s, ztsold, zeta_s, ztstemp, z_s, kjstart = 0 ) 
    759763      CALL wrk_dealloc( jpij, jkmax+2, zindterm, zindtbis, zdiagbis ) 
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/limupdate2.F90

    r4688 r4765  
    211211         DO ji = 1, jpi             
    212212            diag_heat_dhc(ji,jj) = ( SUM( d_e_i_trp(ji,jj,1:nlay_i,:) + d_e_i_thd(ji,jj,1:nlay_i,:) ) +  &  
    213                &                     SUM( d_e_s_trp(ji,jj,1:nlay_s,:) + d_e_s_thd(ji,jj,1:nlay_s,:) ) ) * unit_fac * r1_rdtice / area(ji,jj)    
     213               &                     SUM( d_e_s_trp(ji,jj,1:nlay_s,:) + d_e_s_thd(ji,jj,1:nlay_s,:) )    & 
     214               &                   ) * unit_fac * r1_rdtice / area(ji,jj)    
    214215         END DO 
    215216      END DO 
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90

    r4688 r4765  
    298298      !!---------------------------------------------------------------------- 
    299299 
    300       CALL histdef( kid, "iicethic", "Ice thickness"           , "m"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    301       CALL histdef( kid, "iiceconc", "Ice concentration"       , "%"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    302       CALL histdef( kid, "iicetemp", "Ice temperature"         , "C"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    303       CALL histdef( kid, "iicevelu", "i-Ice speed (I-point)"   , "m/s"    , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    304       CALL histdef( kid, "iicevelv", "j-Ice speed (I-point)"   , "m/s"    , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    305       CALL histdef( kid, "iicestru", "i-Wind stress over ice (I-pt)", "Pa", jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    306       CALL histdef( kid, "iicestrv", "j-Wind stress over ice (I-pt)", "Pa", jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    307       CALL histdef( kid, "iicesflx", "Solar flux over ocean"     , "w/m2"   , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    308       CALL histdef( kid, "iicenflx", "Non-solar flux over ocean" , "w/m2"   , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    309       CALL histdef( kid, "isnowpre", "Snow precipitation"      , "kg/m2/s", jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    310       CALL histdef( kid, "iicesali", "Ice salinity"            , "PSU"    , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    311       CALL histdef( kid, "iicevolu", "Ice volume"              , "m"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    312       CALL histdef( kid, "iicedive", "Ice divergence"          , "10-8s-1", jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    313       CALL histdef( kid, "iicebopr", "Ice bottom production"   , "m/s"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    314       CALL histdef( kid, "iicedypr", "Ice dynamic production"  , "m/s"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    315       CALL histdef( kid, "iicelapr", "Ice open water prod"     , "m/s"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    316       CALL histdef( kid, "iicesipr", "Snow ice production "    , "m/s"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    317       CALL histdef( kid, "iicerepr", "Ice prod from limupdate" , "m/s"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    318       CALL histdef( kid, "iicebome", "Ice bottom melt"         , "m/s"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    319       CALL histdef( kid, "iicesume", "Ice surface melt"        , "m/s"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    320       CALL histdef( kid, "iisfxdyn", "Salt flux from dynmics"  , ""      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    321       CALL histdef( kid, "iisfxres", "Salt flux from limupdate", ""      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     300      CALL histdef( kid, "iicethic", "Ice thickness"           , "m"      ,   & 
     301      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     302      CALL histdef( kid, "iiceconc", "Ice concentration"       , "%"      ,   & 
     303      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     304      CALL histdef( kid, "iicetemp", "Ice temperature"         , "C"      ,   & 
     305      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     306      CALL histdef( kid, "iicevelu", "i-Ice speed (I-point)"   , "m/s"    ,   & 
     307      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     308      CALL histdef( kid, "iicevelv", "j-Ice speed (I-point)"   , "m/s"    ,   & 
     309      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     310      CALL histdef( kid, "iicestru", "i-Wind stress over ice (I-pt)", "Pa",   & 
     311      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     312      CALL histdef( kid, "iicestrv", "j-Wind stress over ice (I-pt)", "Pa",   & 
     313      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     314      CALL histdef( kid, "iicesflx", "Solar flux over ocean"     , "w/m2" ,   & 
     315      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     316      CALL histdef( kid, "iicenflx", "Non-solar flux over ocean" , "w/m2" ,   & 
     317      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     318      CALL histdef( kid, "isnowpre", "Snow precipitation"      , "kg/m2/s",   & 
     319      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     320      CALL histdef( kid, "iicesali", "Ice salinity"            , "PSU"    ,   & 
     321      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     322      CALL histdef( kid, "iicevolu", "Ice volume"              , "m"      ,   & 
     323      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     324      CALL histdef( kid, "iicedive", "Ice divergence"          , "10-8s-1",   & 
     325      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     326      CALL histdef( kid, "iicebopr", "Ice bottom production"   , "m/s"    ,   & 
     327      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     328      CALL histdef( kid, "iicedypr", "Ice dynamic production"  , "m/s"    ,   & 
     329      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     330      CALL histdef( kid, "iicelapr", "Ice open water prod"     , "m/s"    ,   & 
     331      &       jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     332      CALL histdef( kid, "iicesipr", "Snow ice production "    , "m/s"    ,   & 
     333      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     334      CALL histdef( kid, "iicerepr", "Ice prod from limupdate" , "m/s"    ,   & 
     335      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     336      CALL histdef( kid, "iicebome", "Ice bottom melt"         , "m/s"    ,   & 
     337      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     338      CALL histdef( kid, "iicesume", "Ice surface melt"        , "m/s"    ,   & 
     339      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     340      CALL histdef( kid, "iisfxdyn", "Salt flux from dynmics"  , ""       ,   & 
     341      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     342      CALL histdef( kid, "iisfxres", "Salt flux from limupdate", ""       ,   & 
     343      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    322344 
    323345      CALL histend( kid, snc4set )   ! end of the file definition 
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/thd_ice.F90

    r4688 r4765  
    150150         &      fr1_i0_1d(jpij) , fr2_i0_1d(jpij) , qns_ice_1d(jpij) ,     & 
    151151         &      t_bo_b   (jpij) , iatte_1d  (jpij) , oatte_1d (jpij) ,     & 
    152          &      hfx_sum_1d(jpij) , hfx_bom_1d(jpij) ,hfx_bog_1d(jpij) ,hfx_dif_1d(jpij) ,hfx_opw_1d(jpij) , & 
     152         &      hfx_sum_1d(jpij) , hfx_bom_1d(jpij) ,hfx_bog_1d(jpij),     & 
     153         &      hfx_dif_1d(jpij) ,hfx_opw_1d(jpij) , & 
    153154         &      hfx_thd_1d(jpij) , hfx_spr_1d(jpij) , & 
    154          &      hfx_snw_1d(jpij) , hfx_sub_1d(jpij) , hfx_err_1d(jpij) , hfx_res_1d(jpij) , hfx_err_rem_1d(jpij),       STAT=ierr(1) ) 
     155         &      hfx_snw_1d(jpij) , hfx_sub_1d(jpij) , hfx_err_1d(jpij) , & 
     156         &      hfx_res_1d(jpij) , hfx_err_rem_1d(jpij),       STAT=ierr(1) ) 
    155157      ! 
    156158      ALLOCATE( sprecip_1d (jpij) , frld_1d    (jpij) , at_i_b     (jpij) ,     & 
    157159         &      fhtur_1d   (jpij) , wfx_ice_1d (jpij) , wfx_snw_1d (jpij) , wfx_spr_1d (jpij) ,     & 
    158          &      fhld_1d    (jpij) , wfx_sub_1d (jpij) , wfx_bog_1d(jpij) , wfx_bom_1d(jpij) , wfx_sum_1d(jpij) , wfx_sni_1d (jpij) , wfx_opw_1d (jpij) ,  wfx_res_1d (jpij) ,  & 
     160         &      fhld_1d    (jpij) , wfx_sub_1d (jpij) , wfx_bog_1d(jpij) , wfx_bom_1d(jpij) , & 
     161         &      wfx_sum_1d(jpij)  , wfx_sni_1d (jpij) , wfx_opw_1d (jpij) ,  wfx_res_1d (jpij) ,  & 
    159162         &      dqns_ice_1d(jpij) , qla_ice_1d (jpij) , dqla_ice_1d(jpij) ,     & 
    160163         &      tatm_ice_1d(jpij) ,      &    
    161164         &      i0         (jpij) ,     &   
    162          &      sfx_bri_1d (jpij) , sfx_bog_1d (jpij) , sfx_bom_1d (jpij) ,sfx_sum_1d (jpij) ,sfx_sni_1d (jpij) , sfx_opw_1d (jpij) , sfx_res_1d (jpij) , & 
     165         &      sfx_bri_1d (jpij) , sfx_bog_1d (jpij) , sfx_bom_1d (jpij) ,sfx_sum_1d (jpij) ,   & 
     166         &      sfx_sni_1d (jpij) , sfx_opw_1d (jpij) , sfx_res_1d (jpij) , & 
    163167         &      dsm_i_fl_1d(jpij) , dsm_i_gd_1d(jpij) , dsm_i_se_1d(jpij) ,     &      
    164168         &      dsm_i_si_1d(jpij) , hicol_b    (jpij)                     , STAT=ierr(2) ) 
  • trunk/NEMOGCM/NEMO/OPA_SRC/LBC/lib_mpp.F90

    r4671 r4765  
    20842084         IF (l_isend) THEN 
    20852085            DO jr = 1,nsndto 
    2086                IF ((nfipproc(isendto(jr),jpnj) .ne. (narea-1)) .and. (nfipproc(isendto(jr),jpnj) .ne. -1)) CALL mpi_wait(ml_req_nf(jr), ml_stat, ml_err) 
     2086               IF ((nfipproc(isendto(jr),jpnj) .ne. (narea-1)) .and. (nfipproc(isendto(jr),jpnj) .ne. -1)) THEN 
     2087                  CALL mpi_wait(ml_req_nf(jr), ml_stat, ml_err) 
     2088               ENDIF     
    20872089            END DO 
    20882090         ENDIF 
  • trunk/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r4689 r4765  
    160160      IF( lk_cpl ) THEN 
    161161         IF ( ln_iceflx_ave .OR. ln_iceflx_linear ) & 
    162             &   CALL wrk_alloc( jpi,jpj, ztem_ice_all, zalb_ice_all, z_qsr_ice_all, z_qns_ice_all, z_qla_ice_all, z_dqns_ice_all, z_dqla_ice_all) 
     162            &   CALL wrk_alloc( jpi, jpj, ztem_ice_all , zalb_ice_all  , z_qsr_ice_all, z_qns_ice_all,   & 
     163            &                             z_qla_ice_all, z_dqns_ice_all, z_dqla_ice_all) 
    163164      ENDIF 
    164165 
     
    435436      IF( lk_cpl ) THEN 
    436437         IF ( ln_iceflx_ave .OR. ln_iceflx_linear ) & 
    437             &    CALL wrk_dealloc( jpi,jpj, ztem_ice_all, zalb_ice_all, z_qsr_ice_all, z_qns_ice_all, z_qla_ice_all, z_dqns_ice_all, z_dqla_ice_all) 
     438            &    CALL wrk_dealloc( jpi, jpj, ztem_ice_all , zalb_ice_all , z_qsr_ice_all, z_qns_ice_all,   & 
     439            &                                z_qla_ice_all, z_dqns_ice_all, z_dqla_ice_all) 
    438440      ENDIF 
    439441      ! 
Note: See TracChangeset for help on using the changeset viewer.