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 6723 for branches/2016/dev_r6711_SIMPLIF_6_aerobulk/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90 – NEMO

Ignore:
Timestamp:
2016-06-19T11:36:47+02:00 (8 years ago)
Author:
gm
Message:

#1751 - branch SIMPLIF_6_aerobulk: add aerobulk package including NCAR, COARE and ECMWF bulk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r6711_SIMPLIF_6_aerobulk/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r6460 r6723  
    1313   !!            3.4  ! 2011-11  (C. Harris) CICE added as an option 
    1414   !!            3.5  ! 2012-11  (A. Coward, G. Madec) Rethink of heat, mass and salt surface fluxes 
    15    !!            3.6  ! 2014-11  (P. Mathiot, C. Harris) add ice shelves melting                     
     15   !!            3.6  ! 2014-11  (P. Mathiot, C. Harris) add ice shelves melting 
     16   !!            4.0  ! 2016-06  (L. Brodeau) new general bulk formulation 
    1617   !!---------------------------------------------------------------------- 
    1718 
     
    3031   USE sbcana         ! surface boundary condition: analytical formulation 
    3132   USE sbcflx         ! surface boundary condition: flux formulation 
    32    USE sbcblk_clio    ! surface boundary condition: bulk formulation : CLIO 
    33    USE sbcblk_core    ! surface boundary condition: bulk formulation : CORE 
    34    USE sbcblk_mfs     ! surface boundary condition: bulk formulation : MFS 
     33   USE sbcblk         ! surface boundary condition: bulk formulation 
    3534   USE sbcice_if      ! surface boundary condition: ice-if sea-ice model 
    3635   USE sbcice_lim     ! surface boundary condition: LIM 3.0 sea-ice model 
     
    5554   USE timing         ! Timing 
    5655 
    57    USE diurnal_bulk, ONLY: & 
    58       & ln_diurnal_only  
     56   USE diurnal_bulk, ONLY:   ln_diurnal_only 
    5957 
    6058   IMPLICIT NONE 
     
    6361   PUBLIC   sbc        ! routine called by step.F90 
    6462   PUBLIC   sbc_init   ! routine called by opa.F90 
    65     
     63 
    6664   INTEGER ::   nsbc   ! type of surface boundary condition (deduced from namsbc informations) 
    67        
     65 
    6866   !!---------------------------------------------------------------------- 
    69    !! NEMO/OPA 4.0 , NEMO-consortium (2011)  
     67   !! NEMO/OPA 4.0 , NEMO-consortium (2016)  
    7068   !! $Id$ 
    7169   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    8785      INTEGER ::   icpt   ! local integer 
    8886      !! 
    89       NAMELIST/namsbc/ nn_fsbc  , ln_ana   , ln_flx, ln_blk_clio, ln_blk_core, ln_blk_mfs,   & 
    90          &             ln_cpl   , ln_mixcpl, nn_components      , nn_limflx  ,               & 
    91          &             ln_traqsr, ln_dm2dc ,                                                 &   
    92          &             nn_ice   , nn_ice_embd,                                               & 
    93          &             ln_rnf   , ln_ssr   , ln_isf   , nn_fwb    , ln_apr_dyn,              & 
    94          &             ln_wave  ,                                                            & 
    95          &             nn_lsm    
     87      NAMELIST/namsbc/ nn_fsbc  , ln_ana   , ln_flx, ln_blk, ln_cpl   , ln_mixcpl,        & 
     88         &             nn_components      , nn_limflx  ,                                  & 
     89         &             ln_traqsr, ln_dm2dc ,                                              & 
     90         &             nn_ice   , nn_ice_embd,                                            & 
     91         &             ln_rnf   , ln_ssr   , ln_isf   , nn_fwb    , ln_apr_dyn,           & 
     92         &             ln_wave  ,                                                         & 
     93         &             nn_lsm 
    9694      INTEGER  ::   ios 
    9795      INTEGER  ::   ierr, ierr0, ierr1, ierr2, ierr3, jpm 
     
    116114      !                          ! overwrite namelist parameter using CPP key information 
    117115      IF( Agrif_Root() ) THEN                ! AGRIF zoom 
    118         IF( lk_lim2 )   nn_ice      = 2 
    119         IF( lk_lim3 )   nn_ice      = 3 
    120         IF( lk_cice )   nn_ice      = 4 
     116         IF( lk_lim2 )   nn_ice      = 2 
     117         IF( lk_lim3 )   nn_ice      = 3 
     118         IF( lk_cice )   nn_ice      = 4 
    121119      ENDIF 
    122120      IF( cp_cfg == 'gyre' ) THEN            ! GYRE configuration 
    123           ln_ana      = .TRUE.    
    124           nn_ice      =   0 
     121         ln_ana      = .TRUE. 
     122         nn_ice      =   0 
    125123      ENDIF 
    126124      ! 
     
    131129         WRITE(numout,*) '              analytical formulation                     ln_ana        = ', ln_ana 
    132130         WRITE(numout,*) '              flux       formulation                     ln_flx        = ', ln_flx 
    133          WRITE(numout,*) '              CLIO bulk  formulation                     ln_blk_clio   = ', ln_blk_clio 
    134          WRITE(numout,*) '              CORE bulk  formulation                     ln_blk_core   = ', ln_blk_core 
    135          WRITE(numout,*) '              MFS  bulk  formulation                     ln_blk_mfs    = ', ln_blk_mfs 
     131         WRITE(numout,*) '              bulk       formulation                     ln_blk        = ', ln_blk 
    136132         WRITE(numout,*) '           Type of coupling (Ocean/Ice/Atmosphere) : ' 
    137133         WRITE(numout,*) '              ocean-atmosphere coupled formulation       ln_cpl        = ', ln_cpl 
     
    141137         WRITE(numout,*) '              Multicategory heat flux formulation (LIM3) nn_limflx     = ', nn_limflx 
    142138         WRITE(numout,*) '           Sea-ice : ' 
    143          WRITE(numout,*) '              ice management in the sbc (=0/1/2/3)       nn_ice        = ', nn_ice  
     139         WRITE(numout,*) '              ice management in the sbc (=0/1/2/3)       nn_ice        = ', nn_ice 
    144140         WRITE(numout,*) '              ice-ocean embedded/levitating (=0/1/2)     nn_ice_embd   = ', nn_ice_embd 
    145141         WRITE(numout,*) '           Misc. options of sbc : ' 
    146142         WRITE(numout,*) '              Light penetration in temperature Eq.       ln_traqsr     = ', ln_traqsr 
    147          WRITE(numout,*) '                 daily mean to diurnal cycle qsr            ln_dm2dc   = ', ln_dm2dc  
     143         WRITE(numout,*) '                 daily mean to diurnal cycle qsr            ln_dm2dc   = ', ln_dm2dc 
    148144         WRITE(numout,*) '              Sea Surface Restoring on SST and/or SSS    ln_ssr        = ', ln_ssr 
    149145         WRITE(numout,*) '              FreshWater Budget control  (=0/1/2)        nn_fwb        = ', nn_fwb 
     
    153149         WRITE(numout,*) '              closed sea (=0/1) (set in namdom)          nn_closea     = ', nn_closea 
    154150         WRITE(numout,*) '              nb of iterations if land-sea-mask applied  nn_lsm        = ', nn_lsm 
    155          WRITE(numout,*) '              surface wave                               ln_wave       = ', ln_wave   
     151         WRITE(numout,*) '              surface wave                               ln_wave       = ', ln_wave 
    156152      ENDIF 
    157153      ! 
     
    160156         SELECT CASE ( nn_limflx )        ! LIM3 Multi-category heat flux formulation 
    161157         CASE ( -1 )   ;   WRITE(numout,*) '   LIM3: use per-category fluxes (nn_limflx = -1) ' 
    162          CASE ( 0  )   ;   WRITE(numout,*) '   LIM3: use average per-category fluxes (nn_limflx = 0) '  
     158         CASE ( 0  )   ;   WRITE(numout,*) '   LIM3: use average per-category fluxes (nn_limflx = 0) ' 
    163159         CASE ( 1  )   ;   WRITE(numout,*) '   LIM3: use average then redistribute per-category fluxes (nn_limflx = 1) ' 
    164160         CASE ( 2  )   ;   WRITE(numout,*) '   LIM3: Redistribute a single flux over categories (nn_limflx = 2) ' 
     
    185181 
    186182      !                          ! Checks: 
    187       IF( .NOT. ln_isf ) THEN                      ! variable initialisation if no ice shelf  
     183      IF( .NOT. ln_isf ) THEN                      ! variable initialisation if no ice shelf 
    188184         IF( sbc_isf_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_init : unable to allocate sbc_isf arrays' ) 
    189185         fwfisf  (:,:)   = 0.0_wp ; fwfisf_b  (:,:)   = 0.0_wp 
     
    192188      IF( nn_ice == 0 .AND. nn_components /= jp_iam_opa )   fr_i(:,:) = 0._wp    ! no ice in the domain, ice fraction is always zero 
    193189 
    194       sfx(:,:) = 0._wp                             ! the salt flux due to freezing/melting will be computed (i.e. will be non-zero)  
    195                                                    ! only if sea-ice is present 
    196   
     190      sfx(:,:) = 0._wp                             ! the salt flux due to freezing/melting will be computed (i.e. will be non-zero) 
     191      !                                            ! only if sea-ice is present 
     192 
    197193      fmmflx(:,:) = 0._wp                          ! freezing-melting array initialisation 
    198        
     194 
    199195      taum(:,:) = 0._wp                            ! Initialise taum for use in gls in case of reduced restart 
    200196 
    201       !                                            ! restartability    
    202       IF( ( nn_ice == 2 .OR. nn_ice ==3 ) .AND. .NOT.( ln_blk_clio .OR. ln_blk_core .OR. ln_cpl ) )   & 
     197      !                                            ! restartability 
     198      IF( ( nn_ice == 2 .OR. nn_ice ==3 ) .AND. .NOT.( ln_blk .OR. ln_cpl ) )   & 
    203199         &   CALL ctl_stop( 'LIM sea-ice model requires a bulk formulation or coupled configuration' ) 
    204       IF( nn_ice == 4 .AND. .NOT.( ln_blk_core .OR. ln_cpl ) )   & 
    205          &   CALL ctl_stop( 'CICE sea-ice model requires ln_blk_core or ln_cpl' ) 
     200      IF( nn_ice == 4 .AND. .NOT.( ln_blk .OR. ln_cpl ) )   & 
     201         &   CALL ctl_stop( 'CICE sea-ice model requires ln_blk or ln_cpl' ) 
    206202      IF( nn_ice == 4 .AND. lk_agrif )   & 
    207203         &   CALL ctl_stop( 'CICE sea-ice model not currently available with AGRIF' ) 
     
    217213      IF( ln_dm2dc )   nday_qsr = -1   ! initialisation flag 
    218214 
    219       IF( ln_dm2dc .AND. .NOT.( ln_flx .OR. ln_blk_core ) .AND. nn_components /= jp_iam_opa )   & 
    220          &   CALL ctl_stop( 'diurnal cycle into qsr field from daily values requires a flux or core-bulk formulation' ) 
    221        
     215      IF( ln_dm2dc .AND. .NOT.( ln_flx .OR. ln_blk ) .AND. nn_components /= jp_iam_opa )   & 
     216         &   CALL ctl_stop( 'diurnal cycle into qsr field from daily values requires a flux or the bulk formulation' ) 
     217 
    222218      !                          ! Choice of the Surface Boudary Condition (set nsbc) 
    223219      ll_purecpl = ln_cpl .AND. .NOT. ln_mixcpl 
     
    226222      IF( ln_ana          ) THEN   ;   nsbc = jp_ana     ; icpt = icpt + 1   ;   ENDIF       ! analytical           formulation 
    227223      IF( ln_flx          ) THEN   ;   nsbc = jp_flx     ; icpt = icpt + 1   ;   ENDIF       ! flux                 formulation 
    228       IF( ln_blk_clio     ) THEN   ;   nsbc = jp_clio    ; icpt = icpt + 1   ;   ENDIF       ! CLIO bulk            formulation 
    229       IF( ln_blk_core     ) THEN   ;   nsbc = jp_core    ; icpt = icpt + 1   ;   ENDIF       ! CORE bulk            formulation 
    230       IF( ln_blk_mfs      ) THEN   ;   nsbc = jp_mfs     ; icpt = icpt + 1   ;   ENDIF       ! MFS  bulk            formulation 
     224      IF( ln_blk          ) THEN   ;   nsbc = jp_blk     ; icpt = icpt + 1   ;   ENDIF       ! bulk                 formulation 
    231225      IF( ll_purecpl      ) THEN   ;   nsbc = jp_purecpl ; icpt = icpt + 1   ;   ENDIF       ! Pure Coupled         formulation 
    232226      IF( cp_cfg == 'gyre') THEN   ;   nsbc = jp_gyre                        ;   ENDIF       ! GYRE analytical      formulation 
     
    242236         CASE( jp_ana     )   ;   WRITE(numout,*) '   analytical formulation' 
    243237         CASE( jp_flx     )   ;   WRITE(numout,*) '   flux formulation' 
    244          CASE( jp_clio    )   ;   WRITE(numout,*) '   CLIO bulk formulation' 
    245          CASE( jp_core    )   ;   WRITE(numout,*) '   CORE bulk formulation' 
     238         CASE( jp_blk     )   ;   WRITE(numout,*) '   bulk formulation' 
    246239         CASE( jp_purecpl )   ;   WRITE(numout,*) '   pure coupled formulation' 
    247          CASE( jp_mfs     )   ;   WRITE(numout,*) '   MFS Bulk formulation' 
    248240         CASE( jp_none    )   ;   WRITE(numout,*) '   OPA coupled to SAS via oasis' 
    249241            IF( ln_mixcpl )       WRITE(numout,*) '       + forced-coupled mixed formulation' 
     
    269261      ! 
    270262      IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 .OR.   & 
    271           MOD( nstock             , nn_fsbc) /= 0 ) THEN  
     263          MOD( nstock             , nn_fsbc) /= 0 ) THEN 
    272264         WRITE(ctmp1,*) 'experiment length (', nitend - nit000 + 1, ') or nstock (', nstock,   & 
    273265            &           ' is NOT a multiple of nn_fsbc (', nn_fsbc, ')' 
     
    297289      !!--------------------------------------------------------------------- 
    298290      !!                    ***  ROUTINE sbc  *** 
    299       !!               
     291      !! 
    300292      !! ** Purpose :   provide at each time-step the ocean surface boundary 
    301293      !!                condition (momentum, heat and freshwater fluxes) 
    302294      !! 
    303       !! ** Method  :   blah blah  to be written ?????????  
     295      !! ** Method  :   blah blah  to be written ????????? 
    304296      !!                CAUTION : never mask the surface stress field (tke sbc) 
    305297      !! 
    306       !! ** Action  : - set the ocean surface boundary condition at before and now  
    307       !!                time step, i.e.   
     298      !! ** Action  : - set the ocean surface boundary condition at before and now 
     299      !!                time step, i.e. 
    308300      !!                utau_b, vtau_b, qns_b, qsr_b, emp_n, sfx_b, qrp_b, erp_b 
    309301      !!                utau  , vtau  , qns  , qsr  , emp  , sfx  , qrp  , erp 
    310302      !!              - updte the ice fraction : fr_i 
    311303      !!---------------------------------------------------------------------- 
    312       INTEGER, INTENT(in) ::   kt       ! ocean time step 
     304      INTEGER, INTENT(in) ::   kt   ! ocean time step 
     305      ! 
     306      LOGICAL ::   ll_sas, ll_opa   ! local logical 
    313307      !!--------------------------------------------------------------------- 
    314308      ! 
     
    332326      !                                            ! ---------------------------------------- ! 
    333327      ! 
    334       IF( nn_components /= jp_iam_sas )   CALL sbc_ssm ( kt )  ! ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) 
    335       !                                                        ! averaged over nf_sbc time-step 
    336       IF( ln_wave                     )   CALL sbc_wave( kt )  ! surface waves 
    337        
    338        
    339                                                    !==  sbc formulation  ==! 
    340                                                              
     328      ll_sas = nn_components == jp_iam_sas               ! component flags 
     329      ll_opa = nn_components == jp_iam_opa 
     330      ! 
     331      IF( .NOT.ll_sas )   CALL sbc_ssm ( kt )            ! mean ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) 
     332      IF( ln_wave     )   CALL sbc_wave( kt )            ! surface waves 
     333 
     334      ! 
     335      !                                            !==  sbc formulation  ==! 
     336      !                                                    
    341337      SELECT CASE( nsbc )                                ! Compute ocean surface boundary condition 
    342338      !                                                  ! (i.e. utau,vtau, qns, qsr, emp, sfx) 
    343       CASE( jp_gyre  )   ;   CALL sbc_gyre    ( kt )                    ! analytical formulation : GYRE configuration 
    344       CASE( jp_ana   )   ;   CALL sbc_ana     ( kt )                    ! analytical formulation : uniform sbc 
    345       CASE( jp_flx   )   ;   CALL sbc_flx     ( kt )                    ! flux formulation 
    346       CASE( jp_clio  )   ;   CALL sbc_blk_clio( kt )                    ! bulk formulation : CLIO for the ocean 
    347       CASE( jp_core  )    
    348          IF( nn_components == jp_iam_sas ) & 
    349             &                CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: SAS receiving fields from OPA  
    350                              CALL sbc_blk_core( kt )                    ! bulk formulation : CORE for the ocean 
    351                                                                         ! from oce: sea surface variables (sst_m, sss_m,  ssu_m,  ssv_m) 
    352       CASE( jp_purecpl )  ;  CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! pure coupled formulation 
    353                                                                         ! 
    354       CASE( jp_mfs   )   ;   CALL sbc_blk_mfs ( kt )                    ! bulk formulation : MFS for the ocean 
    355       CASE( jp_none  )  
    356          IF( nn_components == jp_iam_opa )   & 
    357             &                CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: OPA receiving fields from SAS 
     339      CASE( jp_gyre    )   ;   CALL sbc_gyre  ( kt )                     ! analytical formulation : GYRE configuration 
     340      CASE( jp_ana     )   ;   CALL sbc_ana   ( kt )                     ! analytical formulation : uniform sbc 
     341      CASE( jp_flx     )   ;   CALL sbc_flx   ( kt )                     ! flux formulation 
     342      CASE( jp_blk     ) 
     343         IF( ll_sas    )       CALL sbc_cpl_rcv( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: SAS receiving fields from OPA 
     344                               CALL sbc_blk    ( kt )                    ! bulk formulation for the ocean 
     345                               ! 
     346      CASE( jp_purecpl )   ;   CALL sbc_cpl_rcv( kt, nn_fsbc, nn_ice )   ! pure coupled formulation 
     347      CASE( jp_none    ) 
     348         IF( ll_opa    )       CALL sbc_cpl_rcv( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: OPA receiving fields from SAS 
    358349      END SELECT 
    359350 
    360       IF( ln_mixcpl )        CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! forced-coupled mixed formulation after forcing 
     351      IF( ln_mixcpl )          CALL sbc_cpl_rcv( kt, nn_fsbc, nn_ice )   ! forced-coupled mixed formulation after forcing 
    361352 
    362353      ! 
     
    368359      CASE(  3 )   ;         CALL sbc_ice_lim  ( kt, nsbc )          ! LIM-3 ice model 
    369360      CASE(  4 )   ;         CALL sbc_ice_cice ( kt, nsbc )          ! CICE ice model 
    370       END SELECT                                               
     361      END SELECT 
    371362 
    372363      IF( ln_icebergs    )   CALL icb_stp( kt )                   ! compute icebergs 
     
    375366 
    376367      IF( ln_rnf         )   CALL sbc_rnf( kt )                   ! add runoffs to fresh water fluxes 
    377   
     368 
    378369      IF( ln_ssr         )   CALL sbc_ssr( kt )                   ! add SST/SSS damping term 
    379370 
    380371      IF( nn_fwb    /= 0 )   CALL sbc_fwb( kt, nn_fwb, nn_fsbc )  ! control the freshwater budget 
    381372 
    382       ! treatment of closed sea in the model domain  
    383       ! (update freshwater fluxes) 
     373      ! treatment of closed sea in the model domain   (update freshwater fluxes) 
    384374      ! Should not be ran if ln_diurnal_only 
    385       IF( .NOT.(ln_diurnal_only) .AND. (nn_closea == 1) )   CALL sbc_clo( kt )    
     375      IF( .NOT.(ln_diurnal_only) .AND. (nn_closea == 1) )   CALL sbc_clo( kt ) 
    386376 
    387377!RBbug do not understand why see ticket 667 
     
    392382         !                                             ! ---------------------------------------- ! 
    393383         IF( ln_rstart .AND.    &                               !* Restart: read in restart file 
    394             & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN  
     384            & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN 
    395385            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields red in the restart file' 
    396386            CALL iom_get( numror, jpdom_autoglo, 'utau_b', utau_b )   ! before i-stress  (U-point) 
     
    408398         ELSE                                                   !* no restart: set from nit000 values 
    409399            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields set to nit000' 
    410             utau_b(:,:) = utau(:,:)  
     400            utau_b(:,:) = utau(:,:) 
    411401            vtau_b(:,:) = vtau(:,:) 
    412402            qns_b (:,:) = qns (:,:) 
    413             emp_b (:,:) = emp(:,:) 
    414             sfx_b (:,:) = sfx(:,:) 
     403            emp_b (:,:) = emp (:,:) 
     404            sfx_b (:,:) = sfx (:,:) 
    415405         ENDIF 
    416406      ENDIF 
     
    436426         CALL iom_put( "empmr"  , emp    - rnf )                ! upward water flux 
    437427         CALL iom_put( "empbmr" , emp_b  - rnf )                ! before upward water flux ( needed to recalculate the time evolution of ssh in offline ) 
    438          CALL iom_put( "saltflx", sfx  )                        ! downward salt flux   
    439                                                                 ! (includes virtual salt flux beneath ice  
    440                                                                 ! in linear free surface case) 
     428         CALL iom_put( "saltflx", sfx  )                        ! downward salt flux (includes virtual salt flux beneath ice in linear free surface case) 
    441429         CALL iom_put( "fmmflx", fmmflx  )                      ! Freezing-melting water flux 
    442          CALL iom_put( "qt"    , qns  + qsr )                   ! total heat flux  
     430         CALL iom_put( "qt"    , qns  + qsr )                   ! total heat flux 
    443431         CALL iom_put( "qns"   , qns        )                   ! solar heat flux 
    444432         CALL iom_put( "qsr"   ,       qsr  )                   ! solar heat flux 
    445          IF( nn_ice > 0 .OR. nn_components == jp_iam_opa )   CALL iom_put( "ice_cover", fr_i )   ! ice fraction  
    446          CALL iom_put( "taum"  , taum       )                   ! wind stress module  
     433         IF( nn_ice > 0 .OR. ll_opa )   CALL iom_put( "ice_cover", fr_i )   ! ice fraction 
     434         CALL iom_put( "taum"  , taum       )                   ! wind stress module 
    447435         CALL iom_put( "wspd"  , wndm       )                   ! wind speed  module over free ocean or leads in presence of sea-ice 
    448436      ENDIF 
    449437      ! 
    450       CALL iom_put( "utau", utau )   ! i-wind stress   (stress can be updated at  
    451       CALL iom_put( "vtau", vtau )   ! j-wind stress    each time step in sea-ice) 
     438      CALL iom_put( "utau", utau )   ! i-wind stress   (stress can be updated at each time step in sea-ice) 
     439      CALL iom_put( "vtau", vtau )   ! j-wind stress 
    452440      ! 
    453441      IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
Note: See TracChangeset for help on using the changeset viewer.