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 8266 for branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO – NEMO

Ignore:
Timestamp:
2017-07-03T12:17:53+02:00 (7 years ago)
Author:
clem
Message:

update outputs following simip requirements

Location:
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r8233 r8266  
    127127      ELSEWHERE                       ;  zalb(:,:) = SUM( alb_ice * a_i_b, dim=3 ) / at_i_b 
    128128      END WHERE 
    129       IF( iom_use('alb_ice' ) )         CALL iom_put( "alb_ice"  , zalb(:,:) )           ! ice albedo output 
     129      IF( iom_use('icealb'  ) )  CALL iom_put( "icealb"   , zalb(:,:) )          ! ice albedo output 
    130130 
    131131      zalb(:,:) = SUM( alb_ice * a_i_b, dim=3 ) + 0.066_wp * ( 1._wp - at_i_b )       
     
    181181 
    182182            ! add the snow melt water to snow mass flux to the ocean 
    183             wfx_snw(:,:)      = wfx_snw(:,:) + wfx_snw_sum(:,:)  
     183            wfx_snw(ji,jj) = wfx_snw(ji,jj) + wfx_snw_sum(ji,jj)  
    184184 
    185185            ! mass flux at the ocean/ice interface 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90

    r8240 r8266  
    5454      ! 
    5555      INTEGER  ::  ji, jj, jk, jl  ! dummy loop indices 
    56       REAL(wp) ::  z2da, z2db, ztmp, zrho1, zrho2 
    57       REAL(wp), POINTER, DIMENSION(:,:,:) ::  zswi2 
    58       REAL(wp), POINTER, DIMENSION(:,:)   ::  z2d, zswi    ! 2D workspace 
    59       REAL(wp), POINTER, DIMENSION(:,:)   ::  zfb          ! ice freeboard 
     56      REAL(wp) ::  z2da, z2db, ztmp, zrho1, zrho2, zmiss_val 
     57      REAL(wp), POINTER, DIMENSION(:,:,:) ::  zswi2, zmiss2 
     58      REAL(wp), POINTER, DIMENSION(:,:)   ::  z2d, zswi, zmiss ! 2D workspace 
     59      REAL(wp), POINTER, DIMENSION(:,:)   ::  zfb              ! ice freeboard 
    6060      REAL(wp), POINTER, DIMENSION(:,:)   ::  zamask, zamask15 ! 15% concentration mask 
    6161 
     
    7272      IF( nn_timing == 1 )  CALL timing_start('limwri') 
    7373 
    74       CALL wrk_alloc( jpi,jpj,jpl, zswi2 ) 
    75       CALL wrk_alloc( jpi,jpj    , z2d, zswi ) 
    76       CALL wrk_alloc( jpi,jpj    , zfb, zamask, zamask15 ) 
    77       !----------------------------- 
    78       ! Mean category values 
    79       !----------------------------- 
     74      CALL wrk_alloc( jpi, jpj, jpl, zswi2, zmiss2 ) 
     75      CALL wrk_alloc( jpi, jpj     , z2d, zswi, zmiss ) 
     76      CALL wrk_alloc( jpi, jpj     , zfb, zamask, zamask15 ) 
     77 
     78      !---------------------------------------- 
     79      ! Brine volume, switches, missing values 
     80      !---------------------------------------- 
    8081 
    8182      ! brine volume 
     
    9798         END DO 
    9899      END DO 
    99       ! 
    100       ! fluxes 
     100 
     101      zmiss_val     = -1.0e20 
     102      zmiss(:,:)    = zmiss_val * ( 1. - zswi(:,:) ) 
     103      zmiss2(:,:,:) = zmiss_val * ( 1. - zswi2(:,:,:) ) 
     104 
     105      !---------------------------------------- 
     106      ! Standard outputs 
     107      !---------------------------------------- 
     108      ! fluxes  
    101109      ! pfrld is the lead fraction at the previous time step (actually between TRP and THD) 
    102110      IF( iom_use('qsr_oce') )   CALL iom_put( "qsr_oce" , qsr_oce(:,:) * pfrld(:,:) )                                   !     solar flux at ocean surface 
     
    114122 
    115123      ! velocity 
    116       IF ( iom_use( "uice_ipa" ) .OR. iom_use( "vice_ipa" ) .OR. iom_use( "icevel" ) ) THEN  
     124      IF ( iom_use('uice_ipa') ) CALL iom_put( "uice_ipa"     , u_ice      )       ! ice velocity u component 
     125      IF ( iom_use('vice_ipa') ) CALL iom_put( "vice_ipa"     , v_ice      )       ! ice velocity v component 
     126 
     127      IF ( ( iom_use( "icevel" ) ) .OR. ( iom_use( "icevel_mv" ) ) ) THEN  
    117128         DO jj = 2 , jpjm1 
    118129            DO ji = 2 , jpim1 
     
    123134         END DO 
    124135         CALL lbc_lnk( z2d, 'T', 1. ) 
    125          CALL iom_put( "uice_ipa"     , u_ice      )       ! ice velocity u component 
    126          CALL iom_put( "vice_ipa"     , v_ice      )       ! ice velocity v component 
    127          CALL iom_put( "icevel"       , z2d        )       ! ice velocity module 
     136         IF ( iom_use( "icevel" )  )   CALL iom_put( "icevel"       , z2d        )                                            ! ice velocity module 
     137         IF ( iom_use( "icevel_mv" ) ) CALL iom_put( "icevel_mv"    , z2d(:,:) * zswi(:,:) + zmiss(:,:) )                     ! ice velocity module (missing value) 
    128138      ENDIF 
    129139 
     
    142152      CALL iom_put( "isnowhc"     , et_s  * zswi        )        ! snow total heat content 
    143153      CALL iom_put( "ibrinv"      , bvm_i * zswi * 100. )        ! brine volume 
    144       CALL iom_put( "utau_ice"    , utau_ice*zswi       )        ! wind stress over ice along i-axis at I-point 
    145       CALL iom_put( "vtau_ice"    , vtau_ice*zswi       )        ! wind stress over ice along j-axis at I-point 
    146154      CALL iom_put( "snowpre"     , sprecip * 86400.    )        ! snow precipitation  
    147155      CALL iom_put( "micesalt"    , smt_i   * zswi      )        ! mean ice salinity 
    148156 
    149       CALL iom_put( "icestr"      , strength * zswi )            ! ice strength 
    150157      CALL iom_put( "idive"       , divu_i              )        ! divergence 
    151158      CALL iom_put( "ishear"      , shear_i             )        ! shear 
     
    257264      zrho1 = ( rau0 - rhoic ) / rau0; zrho2 = rhosn / rau0 
    258265 
    259       IF  ( iom_use( "icethic"  ) ) CALL iom_put( "icethic"     , htm_i * zamask             )          ! Ice thickness  
    260       IF  ( iom_use( "icepres"  ) ) CALL iom_put( "icepres"     , zswi                       )          ! Ice presence (1 or 0)  
    261       IF  ( iom_use( "snowthic" ) ) CALL iom_put( "snowthic"    , htm_s * zamask             )          ! Snow thickness        
    262       IF  ( iom_use( "icemass"  ) ) CALL iom_put( "icemass"     , rhoic * vt_i(:,:) * zswi   )          ! Ice mass per cell area  
    263       IF  ( iom_use( "snomass"  ) ) CALL iom_put( "snomass"     , rhosn * vt_s(:,:) * zswi   )          ! Snow mass per cell area 
    264       IF  ( iom_use( "icesnt"   ) ) CALL iom_put( "icesnt"      , ( tm_si - rt0 ) * zswi     )          ! Snow-ice interface temperature 
    265       IF  ( iom_use( "icebot"   ) ) CALL iom_put( "icebot"      , ( t_bo  - rt0 ) * zswi     )          ! Ice bottom temperature 
    266       IF  ( iom_use( "icesmass" ) ) CALL iom_put( "icesmass"    , SUM( smv_i, DIM = 3 ) * rhoic * 1.0e-3 * zswi )   ! Mass of salt in sea ice per cell area 
     266      IF  ( iom_use( "icepres"  ) ) CALL iom_put( "icepres"     , zswi(:,:)                     )                         ! Ice presence (1 or 0)  
     267      IF  ( iom_use( "icemass"  ) ) CALL iom_put( "icemass"     , rhoic * vt_i(:,:) * zswi(:,:) )                         ! Ice mass per cell area  
     268      IF  ( iom_use( "icethic"  ) ) CALL iom_put( "icethic"     , htm_i(:,:) * zamask(:,:)  * zswi(:,:) + zmiss(:,:) )    ! Ice thickness  
     269      IF  ( iom_use( "snomass"  ) ) CALL iom_put( "snomass"     , rhosn * vt_s(:,:)         * zswi(:,:) + zmiss(:,:) )    ! Snow mass per cell area 
     270      IF  ( iom_use( "snothic"  ) ) CALL iom_put( "snothic"     , htm_s(:,:) * zamask(:,:)  * zswi(:,:) + zmiss(:,:) )    ! Snow thickness        
     271 
     272      IF  ( iom_use( "iceconc_cat_mv"  ) )  CALL iom_put( "iceconc_cat_mv" , a_i(:,:,:)  * zswi2(:,:,:) + zmiss2(:,:,:) ) ! Area for categories 
     273      IF  ( iom_use( "icethic_cat_mv"  ) )  CALL iom_put( "icethic_cat_mv" , ht_i(:,:,:) * zswi2(:,:,:) + zmiss2(:,:,:) ) ! Thickness for categories 
     274      IF  ( iom_use( "snowthic_cat_mv" ) )  CALL iom_put( "snowthic_cat_mv", ht_s(:,:,:) * zswi2(:,:,:) + zmiss2(:,:,:) ) ! Snow depth for categories 
     275 
     276      IF  ( iom_use( "icestK"   ) ) CALL iom_put( "icestK"      , tm_su(:,:)                * zswi(:,:) + zmiss(:,:) )    ! Ice surface temperature 
     277      IF  ( iom_use( "icesntK"  ) ) CALL iom_put( "icesntK"     , tm_si(:,:)                * zswi(:,:) + zmiss(:,:) )    ! Snow-ice interface temperature 
     278      IF  ( iom_use( "icebotK"  ) ) CALL iom_put( "icebotK"     , t_bo(:,:)                 * zswi(:,:) + zmiss(:,:) )    ! Ice bottom temperature 
     279      IF  ( iom_use( "iceage"   ) ) CALL iom_put( "iceage"      , om_i(:,:) * zamask15(:,:) * zswi(:,:) + zmiss(:,:) )    ! Ice age 
     280      IF  ( iom_use( "icesmass" ) ) CALL iom_put( "icesmass"    , SUM( smv_i, dim=3 ) * rhoic * 1.0e-3 * zswi(:,:)   )    ! Mass of salt in sea ice per cell area 
     281      IF  ( iom_use( "icesal"   ) ) CALL iom_put( "icesal"      , smt_i(:,:)                * zswi(:,:) + zmiss(:,:) )    ! Ice salinity 
     282 
    267283      IF  ( iom_use( "icefb"    ) ) THEN 
    268          zfb(:,:) = ( zrho1 * htm_i(:,:) - zrho2 * htm_s(:,:) ) * zswi(:,:)                              
     284         zfb(:,:) = ( zrho1 * htm_i(:,:) - zrho2 * htm_s(:,:) )                                          
    269285         WHERE( zfb < 0._wp ) ;   zfb = 0._wp ;   END WHERE 
    270                                     CALL iom_put( "icefb"       , zfb                        )          ! Ice freeboard 
    271       ENDIF 
    272       IF  ( iom_use( "dmithd"   ) ) CALL iom_put( "dmithd"      , - wfx_bog - wfx_bom - wfx_sum   &     ! Sea-ice mass change from thermodynamics 
     286                                    CALL iom_put( "icefb"       , zfb(:,:)                  * zswi(:,:) + zmiss(:,:) )    ! Ice freeboard 
     287      ENDIF 
     288 
     289      IF  ( iom_use( "isnhcneg" ) ) CALL iom_put( "isnhcneg"    , - et_s(:,:)               * zswi(:,:) + zmiss(:,:) )    ! Snow total heat content 
     290 
     291      IF  ( iom_use( "dmithd"   ) ) CALL iom_put( "dmithd"      , - wfx_bog - wfx_bom - wfx_sum   &                       ! Sea-ice mass change from thermodynamics 
    273292              &                     - wfx_sni - wfx_opw - wfx_res ) 
    274       IF  ( iom_use( "dmidyn"   ) ) CALL iom_put( "dmidyn"      ,   diag_dmi_dyn             )          ! Sea-ice mass change from dynamics 
    275       IF  ( iom_use( "dmiopw"   ) ) CALL iom_put( "dmiopw"      , - wfx_opw                  )          ! Sea-ice mass change through growth in open water 
    276       IF  ( iom_use( "dmibog"   ) ) CALL iom_put( "dmibog"      , - wfx_bog                  )          ! Sea-ice mass change through basal growth 
    277       IF  ( iom_use( "dmisni"   ) ) CALL iom_put( "dmisni"      , - wfx_sni                  )          ! Sea-ice mass change through snow-to-ice conversion 
    278       IF  ( iom_use( "dmisum"   ) ) CALL iom_put( "dmisum"      , - wfx_sum                  )          ! Sea-ice mass change through surface melting 
    279       IF  ( iom_use( "dmibom"   ) ) CALL iom_put( "dmibom"      , - wfx_bom                  )          ! Sea-ice mass change through bottom melting 
    280  
    281       IF  ( iom_use( "dmtsub"   ) ) CALL iom_put( "dmtsub"      , - wfx_sub                  )          ! Sea-ice mass change through evaporation and sublimation 
    282       IF  ( iom_use( "dmssub"   ) ) CALL iom_put( "dmssub"      , - wfx_snw_sub              )          ! Snow mass change through sublimation 
    283       IF  ( iom_use( "dmisub"   ) ) CALL iom_put( "dmisub"      , - wfx_ice_sub              )          ! Sea-ice mass change through sublimation 
    284  
    285       IF  ( iom_use( "dmsspr"   ) ) CALL iom_put( "dmsspr"      , - wfx_spr                  )          ! Snow mass change through snow fall 
    286       IF  ( iom_use( "dmsssi"   ) ) CALL iom_put( "dmsssi"      ,   wfx_sni*rhosn/rhoic      )          ! Snow mass change through snow-to-ice conversion 
    287  
    288       IF  ( iom_use( "dmsmel"   ) ) CALL iom_put( "dmsmel"      , - wfx_snw_sum              )          ! Snow mass change through melt 
    289       IF  ( iom_use( "dmsdyn"   ) ) CALL iom_put( "dmsdyn"      ,   diag_dms_dyn             )          ! Snow mass change through dynamics 
    290  
    291       IF  ( iom_use( "hfxconbo" ) ) CALL iom_put( "hfxconbo"    ,   diag_fc_bo               )          ! Bottom conduction flux 
    292       IF  ( iom_use( "hfxconsu" ) ) CALL iom_put( "hfxconsu"    ,   diag_fc_su               )          ! Surface conduction flux 
    293  
    294       IF  ( iom_use( "wfxtot"   ) ) CALL iom_put( "wfxtot"      ,   wfx_ice                  )          ! Total freshwater flux from sea ice 
    295       IF  ( iom_use( "wfxsum"   ) ) CALL iom_put( "wfxsum"      ,   wfx_sum                  )          ! Freshwater flux from sea-ice surface 
    296  
    297       IF  ( iom_use( "utau_oi"  ) ) CALL iom_put( "utau_oi"     ,   diag_utau_oi*zswi        )          ! X-component of ocean stress on sea ice 
    298       IF  ( iom_use( "vtau_oi"  ) ) CALL iom_put( "vtau_oi"     ,   diag_vtau_oi*zswi        )          ! Y-component of ocean stress on sea ice 
    299  
    300       IF  ( iom_use( "dssh_dx"  ) ) CALL iom_put( "dssh_dx"     ,   diag_dssh_dx*zswi        )          ! Sea-surface tilt term in force balance (x-component) 
    301       IF  ( iom_use( "dssh_dy"  ) ) CALL iom_put( "dssh_dy"     ,   diag_dssh_dy*zswi        )          ! Sea-surface tilt term in force balance (y-component) 
    302  
    303       IF  ( iom_use( "corstrx"  ) ) CALL iom_put( "corstrx"     ,   diag_corstrx*zswi        )          ! Coriolis force term in force balance (x-component) 
    304       IF  ( iom_use( "corstry"  ) ) CALL iom_put( "corstry"     ,   diag_corstry*zswi        )          ! Coriolis force term in force balance (y-component) 
    305  
    306       IF  ( iom_use( "intstrx"  ) ) CALL iom_put( "intstrx"     ,   diag_intstrx*zswi        )          ! Internal force term in force balance (x-component) 
    307       IF  ( iom_use( "intstry"  ) ) CALL iom_put( "intstry"     ,   diag_intstry*zswi        )          ! Internal force term in force balance (y-component) 
    308  
    309       IF  ( iom_use( "normstr"  ) ) CALL iom_put( "normstr"     ,   diag_sig1   *zswi        )          ! Normal stress 
    310       IF  ( iom_use( "sheastr"  ) ) CALL iom_put( "sheastr"     ,   diag_sig2   *zswi        )          ! Shear stress 
    311  
    312       IF  ( iom_use( "xmtrpice" ) ) CALL iom_put( "xmtrpice"     ,  diag_xmtrp_ice           )          ! X-component of sea-ice mass transport 
    313       IF  ( iom_use( "ymtrpice" ) ) CALL iom_put( "ymtrpice"     ,  diag_ymtrp_ice           )          ! Y-component of sea-ice mass transport 
    314  
    315       IF  ( iom_use( "xmtrpsnw" ) ) CALL iom_put( "xmtrpsnw"     ,  diag_xmtrp_snw           )          ! X-component of snow mass transport 
    316       IF  ( iom_use( "ymtrpsnw" ) ) CALL iom_put( "ymtrpsnw"     ,  diag_ymtrp_snw           )          ! Y-component of snow mass transport 
    317  
    318       IF  ( iom_use( "xatrp"    ) ) CALL iom_put( "xatrp"        ,  diag_xatrp               )          ! X-component of ice area transport 
    319       IF  ( iom_use( "yatrp"    ) ) CALL iom_put( "yatrp"        ,  diag_yatrp               )          ! Y-component of ice area transport 
     293      IF  ( iom_use( "dmidyn"   ) ) CALL iom_put( "dmidyn"      ,   diag_dmi_dyn             )                            ! Sea-ice mass change from dynamics 
     294      IF  ( iom_use( "dmiopw"   ) ) CALL iom_put( "dmiopw"      , - wfx_opw                  )                            ! Sea-ice mass change through growth in open water 
     295      IF  ( iom_use( "dmibog"   ) ) CALL iom_put( "dmibog"      , - wfx_bog                  )                            ! Sea-ice mass change through basal growth 
     296      IF  ( iom_use( "dmisni"   ) ) CALL iom_put( "dmisni"      , - wfx_sni                  )                            ! Sea-ice mass change through snow-to-ice conversion 
     297      IF  ( iom_use( "dmisum"   ) ) CALL iom_put( "dmisum"      , - wfx_sum                  )                            ! Sea-ice mass change through surface melting 
     298      IF  ( iom_use( "dmibom"   ) ) CALL iom_put( "dmibom"      , - wfx_bom                  )                            ! Sea-ice mass change through bottom melting 
     299 
     300      IF  ( iom_use( "dmtsub"   ) ) CALL iom_put( "dmtsub"      , - wfx_sub                  )                            ! Sea-ice mass change through evaporation and sublimation 
     301      IF  ( iom_use( "dmssub"   ) ) CALL iom_put( "dmssub"      , - wfx_snw_sub              )                            ! Snow mass change through sublimation 
     302      IF  ( iom_use( "dmisub"   ) ) CALL iom_put( "dmisub"      , - wfx_ice_sub              )                            ! Sea-ice mass change through sublimation 
     303 
     304      IF  ( iom_use( "dmsspr"   ) ) CALL iom_put( "dmsspr"      , - wfx_spr                  )                            ! Snow mass change through snow fall 
     305      IF  ( iom_use( "dmsssi"   ) ) CALL iom_put( "dmsssi"      ,   wfx_sni*rhosn/rhoic      )                            ! Snow mass change through snow-to-ice conversion 
     306 
     307      IF  ( iom_use( "dmsmel"   ) ) CALL iom_put( "dmsmel"      , - wfx_snw_sum              )                            ! Snow mass change through melt 
     308      IF  ( iom_use( "dmsdyn"   ) ) CALL iom_put( "dmsdyn"      ,   diag_dms_dyn             )                            ! Snow mass change through dynamics 
     309 
     310      IF  ( iom_use( "hfxsenso" ) ) CALL iom_put( "hfxsenso"    ,   -fhtur(:,:)              * zswi(:,:) + zmiss(:,:) )   ! Sensible oceanic heat flux 
     311      IF  ( iom_use( "hfxconbo" ) ) CALL iom_put( "hfxconbo"    ,   diag_fc_bo               * zswi(:,:) + zmiss(:,:) )   ! Bottom conduction flux 
     312      IF  ( iom_use( "hfxconsu" ) ) CALL iom_put( "hfxconsu"    ,   diag_fc_su               * zswi(:,:) + zmiss(:,:) )   ! Surface conduction flux 
     313 
     314      IF  ( iom_use( "wfxtot"   ) ) CALL iom_put( "wfxtot"      ,   wfx_ice(:,:)             * zswi(:,:) + zmiss(:,:) )   ! Total freshwater flux from sea ice 
     315      IF  ( iom_use( "wfxsum"   ) ) CALL iom_put( "wfxsum"      ,   wfx_sum(:,:)             * zswi(:,:) + zmiss(:,:) )   ! Freshwater flux from sea-ice surface 
     316      IF  ( iom_use( "sfx_mv"   ) ) CALL iom_put( "sfx_mv"      ,   sfx(:,:) * 0.001         * zswi(:,:) + zmiss(:,:) )   ! Total salt flux 
     317 
     318      IF  ( iom_use( "uice_mv"  ) ) CALL iom_put( "uice_mv"     ,   u_ice(:,:)               * zswi(:,:) + zmiss(:,:) )   ! ice velocity u component 
     319      IF  ( iom_use( "vice_mv"  ) ) CALL iom_put( "vice_mv"     ,   v_ice(:,:)               * zswi(:,:) + zmiss(:,:) )   ! ice velocity v component 
     320       
     321      IF  ( iom_use( "xmtrpice" ) ) CALL iom_put( "xmtrpice"     ,  diag_xmtrp_ice(:,:)      )                            ! X-component of sea-ice mass transport (kg/s) 
     322      IF  ( iom_use( "ymtrpice" ) ) CALL iom_put( "ymtrpice"     ,  diag_ymtrp_ice(:,:)      )                            ! Y-component of sea-ice mass transport  
     323 
     324      IF  ( iom_use( "xmtrpsnw" ) ) CALL iom_put( "xmtrpsnw"     ,  diag_xmtrp_snw(:,:)      )                            ! X-component of snow mass transport (kg/s) 
     325      IF  ( iom_use( "ymtrpsnw" ) ) CALL iom_put( "ymtrpsnw"     ,  diag_ymtrp_snw(:,:)      )                            ! Y-component of snow mass transport 
     326 
     327      IF  ( iom_use( "xatrp"    ) ) CALL iom_put( "xatrp"        ,  diag_xatrp(:,:)              )                        ! X-component of ice area transport 
     328      IF  ( iom_use( "yatrp"    ) ) CALL iom_put( "yatrp"        ,  diag_yatrp(:,:)              )                        ! Y-component of ice area transport 
     329 
     330      IF  ( iom_use( "utau_ice" ) ) CALL iom_put( "utau_ice"     ,  utau_ice(:,:)            * zswi(:,:) + zmiss(:,:) )   ! Wind stress term in force balance (x) 
     331      IF  ( iom_use( "vtau_ice" ) ) CALL iom_put( "vtau_ice"     ,  vtau_ice(:,:)            * zswi(:,:) + zmiss(:,:) )   ! Wind stress term in force balance (y) 
     332 
     333      IF  ( iom_use( "utau_oi"  ) ) CALL iom_put( "utau_oi"     ,   diag_utau_oi(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Ocean stress term in force balance (x) 
     334      IF  ( iom_use( "vtau_oi"  ) ) CALL iom_put( "vtau_oi"     ,   diag_vtau_oi(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Ocean stress term in force balance (y) 
     335 
     336      IF  ( iom_use( "icestr"   ) ) CALL iom_put( "icestr"      ,   strength(:,:)            * zswi(:,:) + zmiss(:,:) )   ! Ice strength 
     337 
     338      IF  ( iom_use( "dssh_dx"  ) ) CALL iom_put( "dssh_dx"     ,   diag_dssh_dx(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Sea-surface tilt term in force balance (x) 
     339      IF  ( iom_use( "dssh_dy"  ) ) CALL iom_put( "dssh_dy"     ,   diag_dssh_dy(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Sea-surface tilt term in force balance (y) 
     340 
     341      IF  ( iom_use( "corstrx"  ) ) CALL iom_put( "corstrx"     ,   diag_corstrx(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Coriolis force term in force balance (x) 
     342      IF  ( iom_use( "corstry"  ) ) CALL iom_put( "corstry"     ,   diag_corstry(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Coriolis force term in force balance (y) 
     343 
     344      IF  ( iom_use( "intstrx"  ) ) CALL iom_put( "intstrx"     ,   diag_intstrx(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Internal force term in force balance (x) 
     345      IF  ( iom_use( "intstry"  ) ) CALL iom_put( "intstry"     ,   diag_intstry(:,:)        * zswi(:,:) + zmiss(:,:) )   ! Internal force term in force balance (y) 
     346 
     347      IF  ( iom_use( "normstr"  ) ) CALL iom_put( "normstr"     ,   diag_sig1(:,:) * zswi(:,:)   )                        ! Normal stress 
     348      IF  ( iom_use( "sheastr"  ) ) CALL iom_put( "sheastr"     ,   diag_sig2(:,:) * zswi(:,:)   )                        ! Shear stress 
    320349 
    321350      !-------------------------------- 
     
    369398      !     not yet implemented 
    370399       
    371       CALL wrk_dealloc( jpi, jpj, jpl, zswi2 ) 
    372       CALL wrk_dealloc( jpi, jpj     , z2d, zswi ) 
     400      CALL wrk_dealloc( jpi, jpj, jpl, zswi2, zmiss2 ) 
     401      CALL wrk_dealloc( jpi, jpj     , z2d, zswi, zmiss ) 
    373402      CALL wrk_dealloc( jpi, jpj     , zfb, zamask, zamask15 ) 
    374403 
Note: See TracChangeset for help on using the changeset viewer.