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 4558 for trunk – NEMO

Changeset 4558 for trunk


Ignore:
Timestamp:
2014-03-19T10:35:49+01:00 (10 years ago)
Author:
clem
Message:

update diags in diahsb

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90

    r4333 r4558  
    3636   LOGICAL, PUBLIC ::   ln_diahsb   !: check the heat and salt budgets 
    3737 
    38    REAL(wp), SAVE                                ::   frc_t      , frc_s     , frc_v   ! global forcing trends 
    39    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ssh_ini              ! 
    40    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hc_loc_ini, sc_loc_ini, e3t_ini  ! 
    41    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hcssh_loc_ini, scssh_loc_ini     ! 
     38   REAL(dp)                                ::   surf_tot                ! 
     39   REAL(dp)                                ::   frc_t      , frc_s     , frc_v   ! global forcing trends 
     40   REAL(dp)                                ::   frc_wn_t      , frc_wn_s ! global forcing trends 
     41   REAL(dp), DIMENSION(:,:)  , ALLOCATABLE ::   surf      , ssh_ini              ! 
     42   REAL(dp), DIMENSION(:,:,:), ALLOCATABLE ::   hc_loc_ini, sc_loc_ini, e3t_ini  ! 
     43   REAL(dp), DIMENSION(:,:)  , ALLOCATABLE ::   ssh_hc_loc_ini, ssh_sc_loc_ini 
    4244 
    4345   !! * Substitutions 
     
    6769      !! 
    6870      INTEGER    ::   jk                          ! dummy loop indice 
    69       REAL(wp)   ::   zdiff_hc    , zdiff_sc      ! heat and salt content variations 
    70       REAL(wp)   ::   zdiff_v1    , zdiff_v2      ! volume variation 
    71       REAL(wp)   ::   z_hc        , z_sc          ! heat and salt content 
    72       REAL(wp)   ::   z_v1        , z_v2          ! volume 
    73       REAL(wp)   ::   zdeltat                     !    -     - 
    74       REAL(wp)   ::   z_frc_trd_t , z_frc_trd_s   !    -     - 
    75       REAL(wp)   ::   z_frc_trd_v                 !    -     - 
    76       REAL(wp), POINTER, DIMENSION(:,:)   ::   zsurf              ! 
     71      REAL(dp)   ::   zdiff_hc    , zdiff_sc      ! heat and salt content variations 
     72      REAL(dp)   ::   zdiff_hc1   , zdiff_sc1     ! -   -   -   -   -   -   -   -  
     73      REAL(dp)   ::   zdiff_v1    , zdiff_v2      ! volume variation 
     74      REAL(dp)   ::   zerr_hc1    , zerr_sc1       ! heat and salt content misfit 
     75      REAL(dp)   ::   zvol_tot                    ! volume 
     76      REAL(dp)   ::   z_frc_trd_t , z_frc_trd_s   !    -     - 
     77      REAL(dp)   ::   z_frc_trd_v                 !    -     - 
     78      REAL(dp)   ::   z_wn_trd_t , z_wn_trd_s   !    -     - 
     79      REAL(dp)   ::   z_ssh_hc , z_ssh_sc   !    -     - 
    7780      !!--------------------------------------------------------------------------- 
    7881      IF( nn_timing == 1 )   CALL timing_start('dia_hsb')       
    7982 
    80       CALL wrk_alloc( jpi, jpj, zsurf ) 
    81    
    82       zsurf(:,:) = e1t(:,:) * e2t(:,:) * tmask(:,:,1) * tmask_i(:,:)      ! masked surface grid cell area 
    83        
    8483      ! ------------------------- ! 
    8584      ! 1 - Trends due to forcing ! 
    8685      ! ------------------------- ! 
    87       z_frc_trd_v = r1_rau0 * glob_sum( - ( emp(:,:) - rnf(:,:) ) * zsurf(:,:) ) ! volume fluxes 
    88       z_frc_trd_t =           glob_sum( sbc_tsc(:,:,jp_tem) * zsurf(:,:) )       ! heat fluxes 
    89       z_frc_trd_s =           glob_sum( sbc_tsc(:,:,jp_sal) * zsurf(:,:) )       ! salt fluxes 
    90       ! 
    91       IF( ln_rnf    )   z_frc_trd_t = z_frc_trd_t + glob_sum( rnf_tsc(:,:,jp_tem) * zsurf(:,:) ) 
    92       IF( ln_rnf_sal)   z_frc_trd_s = z_frc_trd_s + glob_sum( rnf_tsc(:,:,jp_sal) * zsurf(:,:) ) 
     86      z_frc_trd_v = r1_rau0 * glob_sum( - ( emp(:,:) - rnf(:,:) ) * surf(:,:) ) ! volume fluxes 
     87      z_frc_trd_t =           glob_sum( sbc_tsc(:,:,jp_tem) * surf(:,:) )       ! heat fluxes 
     88      z_frc_trd_s =           glob_sum( sbc_tsc(:,:,jp_sal) * surf(:,:) )       ! salt fluxes 
     89      ! Add runoff heat & salt input 
     90      IF( ln_rnf    )   z_frc_trd_t = z_frc_trd_t + glob_sum( rnf_tsc(:,:,jp_tem) * surf(:,:) ) 
     91      IF( ln_rnf_sal)   z_frc_trd_s = z_frc_trd_s + glob_sum( rnf_tsc(:,:,jp_sal) * surf(:,:) ) 
    9392 
    9493      ! Add penetrative solar radiation 
    95       IF( ln_traqsr )   z_frc_trd_t = z_frc_trd_t + r1_rau0_rcp * glob_sum( qsr     (:,:) * zsurf(:,:) ) 
     94      IF( ln_traqsr )   z_frc_trd_t = z_frc_trd_t + r1_rau0_rcp * glob_sum( qsr     (:,:) * surf(:,:) ) 
    9695      ! Add geothermal heat flux 
    97       IF( ln_trabbc )   z_frc_trd_t = z_frc_trd_t +               glob_sum( qgh_trd0(:,:) * zsurf(:,:) ) 
    98       ! 
     96      IF( ln_trabbc )   z_frc_trd_t = z_frc_trd_t +               glob_sum( qgh_trd0(:,:) * surf(:,:) ) 
     97      ! 
     98      IF( .NOT. lk_vvl ) THEN 
     99         z_wn_trd_t = - glob_sum( surf(:,:) * wn(:,:,1) * tsb(:,:,1,jp_tem) ) 
     100         z_wn_trd_s = - glob_sum( surf(:,:) * wn(:,:,1) * tsb(:,:,1,jp_sal) ) 
     101      ENDIF 
     102 
    99103      frc_v = frc_v + z_frc_trd_v * rdt 
    100104      frc_t = frc_t + z_frc_trd_t * rdt 
    101105      frc_s = frc_s + z_frc_trd_s * rdt 
     106      !                                          ! Advection flux through fixed surface (z=0) 
     107      IF( .NOT. lk_vvl ) THEN 
     108         frc_wn_t = frc_wn_t + z_wn_trd_t * rdt 
     109         frc_wn_s = frc_wn_s + z_wn_trd_s * rdt 
     110      ENDIF 
    102111 
    103112      ! ------------------------ ! 
    104       ! 2a -  Content variations ! 
     113      ! 2 -  Content variations ! 
    105114      ! ------------------------ ! 
    106       zdiff_v2 = 0._wp 
    107       zdiff_hc = 0._wp 
    108       zdiff_sc = 0._wp 
     115      zdiff_v2 = 0.d0 
     116      zdiff_hc = 0.d0 
     117      zdiff_sc = 0.d0 
     118 
    109119      ! volume variation (calculated with ssh) 
    110       zdiff_v1 = glob_sum( zsurf(:,:) * ( sshn(:,:) - ssh_ini(:,:) ) ) 
     120      zdiff_v1 = glob_sum( surf(:,:) * ( sshn(:,:) - ssh_ini(:,:) ) ) 
     121 
     122      ! heat & salt content variation (associated with ssh) 
     123      IF( .NOT. lk_vvl ) THEN 
     124         z_ssh_hc = glob_sum( surf(:,:) * ( tsn(:,:,1,jp_tem) * sshn(:,:) - ssh_hc_loc_ini(:,:) ) ) 
     125         z_ssh_sc = glob_sum( surf(:,:) * ( tsn(:,:,1,jp_sal) * sshn(:,:) - ssh_sc_loc_ini(:,:) ) ) 
     126      ENDIF 
     127 
    111128      DO jk = 1, jpkm1 
    112129         ! volume variation (calculated with scale factors) 
    113          zdiff_v2 = zdiff_v2 + glob_sum( zsurf(:,:) * tmask(:,:,jk) * ( fse3t_n(:,:,jk) - e3t_ini(:,:,jk) ) ) 
     130         zdiff_v2 = zdiff_v2 + glob_sum( surf(:,:) * tmask(:,:,jk) & 
     131            &                           * ( fse3t_n(:,:,jk) - e3t_ini(:,:,jk) ) ) 
    114132         ! heat content variation 
    115          zdiff_hc = zdiff_hc + glob_sum( zsurf(:,:) * tmask(:,:,jk) * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_tem)   & 
    116             &                           - hc_loc_ini(:,:,jk) ) ) 
     133         zdiff_hc = zdiff_hc + glob_sum(  surf(:,:) * tmask(:,:,jk) &  
     134            &                           * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_tem) - hc_loc_ini(:,:,jk) ) ) 
    117135         ! salt content variation 
    118          zdiff_sc = zdiff_sc + glob_sum( zsurf(:,:) * tmask(:,:,jk) * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_sal)   & 
    119             &                           - sc_loc_ini(:,:,jk) ) ) 
     136         zdiff_sc = zdiff_sc + glob_sum(  surf(:,:) * tmask(:,:,jk)   & 
     137            &                           * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_sal) - sc_loc_ini(:,:,jk) ) ) 
    120138      ENDDO 
    121139 
    122140      ! Substract forcing from heat content, salt content and volume variations 
    123       !frc_v = zdiff_v2 - frc_v 
    124       !frc_t = zdiff_hc - frc_t 
    125       !frc_s = zdiff_sc - frc_s 
    126        
    127       ! add ssh if not vvl 
     141      zdiff_v1 = zdiff_v1 - frc_v 
     142      IF( lk_vvl )   zdiff_v2 = zdiff_v2 - frc_v 
     143      zdiff_hc = zdiff_hc - frc_t 
     144      zdiff_sc = zdiff_sc - frc_s 
    128145      IF( .NOT. lk_vvl ) THEN 
    129         zdiff_v2 = zdiff_v2 + zdiff_v1 
    130         zdiff_hc = zdiff_hc + glob_sum( zsurf(:,:) * ( sshn(:,:) * tsn(:,:,1,jp_tem)   & 
    131                &                           - hcssh_loc_ini(:,:) ) ) 
    132         zdiff_sc = zdiff_sc + glob_sum( zsurf(:,:) * ( sshn(:,:) * tsn(:,:,1,jp_sal)   & 
    133                &                           - scssh_loc_ini(:,:) ) ) 
    134       ENDIF 
    135       ! 
    136       ! ----------------------- ! 
    137       ! 2b -  Content           ! 
    138       ! ----------------------- ! 
    139       z_v2 = 0._wp 
    140       z_hc = 0._wp 
    141       z_sc = 0._wp 
    142       ! volume (calculated with ssh) 
    143       z_v1 = glob_sum( zsurf(:,:) * sshn(:,:) ) 
    144       DO jk = 1, jpkm1 
    145          ! volume (calculated with scale factors) 
    146          z_v2 = z_v2 + glob_sum( zsurf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) ) 
    147          ! heat content 
    148          z_hc = z_hc + glob_sum( zsurf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) * tsn(:,:,jk,jp_tem) ) 
    149          ! salt content 
    150          z_sc = z_sc + glob_sum( zsurf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) * tsn(:,:,jk,jp_sal) ) 
    151       ENDDO 
    152       ! add ssh if not vvl 
    153       IF( .NOT. lk_vvl ) THEN 
    154         z_v2 = z_v2 + z_v1 
    155         z_hc = z_hc + glob_sum( zsurf(:,:) * sshn(:,:) * tsn(:,:,1,jp_tem) ) 
    156         z_sc = z_sc + glob_sum( zsurf(:,:) * sshn(:,:) * tsn(:,:,1,jp_sal) ) 
     146         zdiff_hc1 = zdiff_hc + z_ssh_hc  
     147         zdiff_sc1 = zdiff_sc + z_ssh_sc 
     148         zerr_hc1  = z_ssh_hc - frc_wn_t 
     149         zerr_sc1  = z_ssh_sc - frc_wn_s 
    157150      ENDIF 
    158151 
     
    160153      ! 3 - Diagnostics writing ! 
    161154      ! ----------------------- ! 
    162       zdeltat  = 1.e0 / ( ( kt - nit000 + 1 ) * rdt ) 
    163 ! 
    164       CALL iom_put( 'bgtemper' , z_hc / z_v2 )                      ! Temperature (C)  
    165       CALL iom_put( 'bgsaline' , z_sc / z_v2 )                      ! Salinity (psu) 
    166       CALL iom_put( 'bgheatco' , zdiff_hc * rau0 * rcp * 1.e-9_wp ) ! Heat content variation (10^9 J) 
    167       CALL iom_put( 'bgsaltco' , zdiff_sc * 1.e-9 )                 ! Salt content variation (psu*km3)  
    168       CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9 )                    ! volume ssh (km3)   
    169       CALL iom_put( 'bgsshtot' , zdiff_v1 / glob_sum(zsurf) )          ! ssh (m)   
    170       CALL iom_put( 'bgvoltot' , zdiff_v2 * 1.e-9 )                 ! volume total (km3)  
    171       CALL iom_put( 'bgfrcvol' , frc_v * 1.e-9 )                     ! vol - surface forcing (volume)  
    172       CALL iom_put( 'bgfrctem' , frc_t * rau0 * rcp * 1.e-9_wp ) ! hc  - surface forcing (heat content)  
    173       CALL iom_put( 'bgfrcsal' , frc_s * 1.e-9 )                     ! sc  - surface forcing (salt content)  
    174       ! 
    175       CALL wrk_dealloc( jpi, jpj, zsurf ) 
    176       ! 
     155      zvol_tot   = 0.d0                                                   ! total ocean volume 
     156      DO jk = 1, jpkm1 
     157         zvol_tot  = zvol_tot + glob_sum( surf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) ) 
     158      END DO 
     159 
     160      IF( lk_vvl ) THEN 
     161        CALL iom_put( 'bgtemper' , zdiff_hc / zvol_tot )              ! Temperature variation (C)  
     162        CALL iom_put( 'bgsaline' , zdiff_sc / zvol_tot )              ! Salinity    variation (psu) 
     163        CALL iom_put( 'bgheatco' , zdiff_hc * 1.e-20 * rau0 * rcp )   ! Heat content variation (1.e20 J)  
     164        CALL iom_put( 'bgsaltco' , zdiff_sc * 1.e-9    )              ! Salt content variation (psu*km3) 
     165        CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9    )              ! volume ssh variation (km3)   
     166        CALL iom_put( 'bgvole3t' , zdiff_v2 * 1.e-9    )              ! volume e3t variation (km3)   
     167        CALL iom_put( 'bgfrcvol' , frc_v    * 1.e-9    )              ! vol - surface forcing (km3)  
     168        CALL iom_put( 'bgfrctem' , frc_t / zvol_tot    )              ! hc  - surface forcing (C)  
     169        CALL iom_put( 'bgfrcsal' , frc_s / zvol_tot    )              ! sc  - surface forcing (psu)  
     170      ELSE 
     171        CALL iom_put( 'bgtemper' , zdiff_hc1 / zvol_tot)              ! Heat content variation (C)  
     172        CALL iom_put( 'bgsaline' , zdiff_sc1 / zvol_tot)              ! Salt content variation (psu) 
     173        CALL iom_put( 'bgheatco' , zdiff_hc1 * 1.e-20 * rau0 * rcp )  ! Heat content variation (1.e20 J)  
     174        CALL iom_put( 'bgsaltco' , zdiff_sc1 * 1.e-9    )             ! Salt content variation (psu*km3) 
     175        CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9    )              ! volume ssh variation (km3)   
     176        CALL iom_put( 'bgfrcvol' , frc_v    * 1.e-9    )              ! vol - surface forcing (km3)  
     177        CALL iom_put( 'bgfrctem' , frc_t / zvol_tot    )              ! hc  - surface forcing (C)  
     178        CALL iom_put( 'bgfrcsal' , frc_s / zvol_tot    )              ! sc  - surface forcing (psu)  
     179        CALL iom_put( 'bgmistem' , zerr_hc1 / zvol_tot )              ! hc  - error due to free surface (C) 
     180        CALL iom_put( 'bgmissal' , zerr_sc1 / zvol_tot )              ! sc  - error due to free surface (psu) 
     181      ENDIF 
     182      ! 
     183      IF( lrst_oce )   CALL dia_hsb_rst( kt, 'WRITE' ) 
     184 
    177185      IF( nn_timing == 1 )   CALL timing_stop('dia_hsb') 
    178186! 
     
    222230         WRITE(numout,*) '   Namelist namhsb : set hsb parameters' 
    223231         WRITE(numout,*) '      Switch for hsb diagnostic (T) or not (F)  ln_diahsb  = ', ln_diahsb 
     232         WRITE(numout,*) 
    224233      ENDIF 
    225234 
    226235      IF( .NOT. ln_diahsb )   RETURN 
    227  
    228          ! ------------------- ! 
    229          ! 1 - Allocate memory ! 
    230          ! ------------------- ! 
    231          ALLOCATE( hc_loc_ini(jpi,jpj,jpk), STAT=ierror ) 
    232          IF( ierror > 0 ) THEN 
    233             CALL ctl_stop( 'dia_hsb: unable to allocate hc_loc_ini' )   ;   RETURN 
    234          ENDIF 
    235          ALLOCATE( sc_loc_ini(jpi,jpj,jpk), STAT=ierror ) 
    236          IF( ierror > 0 ) THEN 
    237             CALL ctl_stop( 'dia_hsb: unable to allocate sc_loc_ini' )   ;   RETURN 
    238          ENDIF 
    239          ALLOCATE( hcssh_loc_ini(jpi,jpj), STAT=ierror ) 
    240          IF( ierror > 0 ) THEN 
    241             CALL ctl_stop( 'dia_hsb: unable to allocate hcssh_loc_ini' )   ;   RETURN 
    242          ENDIF 
    243          ALLOCATE( scssh_loc_ini(jpi,jpj), STAT=ierror ) 
    244          IF( ierror > 0 ) THEN 
    245             CALL ctl_stop( 'dia_hsb: unable to allocate scssh_loc_ini' )   ;   RETURN 
    246          ENDIF 
    247          ALLOCATE( e3t_ini(jpi,jpj,jpk)   , STAT=ierror ) 
    248          IF( ierror > 0 ) THEN 
    249             CALL ctl_stop( 'dia_hsb: unable to allocate e3t_ini' )      ;   RETURN 
    250          ENDIF 
    251          ALLOCATE( ssh_ini(jpi,jpj)       , STAT=ierror ) 
    252          IF( ierror > 0 ) THEN 
    253             CALL ctl_stop( 'dia_hsb: unable to allocate ssh_ini' )      ;   RETURN 
    254          ENDIF 
    255           
    256          ! ----------------------------------------------- ! 
    257          ! 2 - Time independant variables and file opening ! 
    258          ! ----------------------------------------------- ! 
    259          IF(lwp) WRITE(numout,*) "dia_hsb: heat salt volume budgets activated" 
    260          IF( lk_bdy ) THEN 
    261             CALL ctl_warn( 'dia_hsb does not take open boundary fluxes into account' )          
    262          ENDIF 
    263          ! 
    264          CALL dia_hsb_rst( nit000, 'READ' )  !* read or initialize all required files 
     236!      IF( .NOT. lk_mpp_rep ) & 
     237!        CALL ctl_stop (' Your global mpp_sum if performed in single precision - 64 bits -', & 
     238!             &         ' whereas the global sum to be precise must be done in double precision ',& 
     239!             &         ' please add key_mpp_rep') 
     240 
     241      ! ------------------- ! 
     242      ! 1 - Allocate memory ! 
     243      ! ------------------- ! 
     244      ALLOCATE( hc_loc_ini(jpi,jpj,jpk), sc_loc_ini(jpi,jpj,jpk), & 
     245         &      e3t_ini(jpi,jpj,jpk), surf(jpi,jpj),  ssh_ini(jpi,jpj), STAT=ierror ) 
     246      IF( ierror > 0 ) THEN 
     247         CALL ctl_stop( 'dia_hsb: unable to allocate hc_loc_ini' )   ;   RETURN 
     248      ENDIF 
     249 
     250      IF(.NOT. lk_vvl ) ALLOCATE( ssh_hc_loc_ini(jpi,jpj), ssh_sc_loc_ini(jpi,jpj),STAT=ierror ) 
     251      IF( ierror > 0 ) THEN 
     252         CALL ctl_stop( 'dia_hsb: unable to allocate hc_loc_ini' )   ;   RETURN 
     253      ENDIF 
     254 
     255      ! ----------------------------------------------- ! 
     256      ! 2 - Time independant variables and file opening ! 
     257      ! ----------------------------------------------- ! 
     258      IF(lwp) WRITE(numout,*) "dia_hsb: heat salt volume budgets activated" 
     259      IF(lwp) WRITE(numout,*) '~~~~~~~' 
     260      surf(:,:) = e1t(:,:) * e2t(:,:) * tmask(:,:,1) * tmask_i(:,:)      ! masked surface grid cell area 
     261      surf_tot  = glob_sum( surf(:,:) )                                       ! total ocean surface area 
     262 
     263      IF( lk_bdy ) CALL ctl_warn( 'dia_hsb does not take open boundary fluxes into account' )          
     264      ! 
     265      ! ---------------------------------- ! 
     266      ! 4 - initial conservation variables ! 
     267      ! ---------------------------------- ! 
     268      CALL dia_hsb_rst( nit000, 'READ' )  !* read or initialize all required files 
    265269      ! 
    266270   END SUBROUTINE dia_hsb_init 
     
    285289           !id1 = iom_varid( numror, 'frc_vol'  , ldstop = .FALSE. ) 
    286290           ! 
     291           IF(lwp) WRITE(numout,*) '~~~~~~~' 
     292           IF(lwp) WRITE(numout,*) ' dia_hsb_rst at it= ', kt,' date= ', ndastp 
     293           IF(lwp) WRITE(numout,*) '~~~~~~~' 
    287294           CALL iom_get( numror, 'frc_v', frc_v ) 
    288295           CALL iom_get( numror, 'frc_t', frc_t ) 
    289296           CALL iom_get( numror, 'frc_s', frc_s ) 
    290  
     297           IF( .NOT. lk_vvl ) THEN 
     298              CALL iom_get( numror, 'frc_wn_t', frc_wn_t ) 
     299              CALL iom_get( numror, 'frc_wn_s', frc_wn_s ) 
     300           ENDIF 
    291301           CALL iom_get( numror, jpdom_autoglo, 'ssh_ini', ssh_ini ) 
    292302           CALL iom_get( numror, jpdom_autoglo, 'e3t_ini', e3t_ini ) 
    293303           CALL iom_get( numror, jpdom_autoglo, 'hc_loc_ini', hc_loc_ini ) 
    294304           CALL iom_get( numror, jpdom_autoglo, 'sc_loc_ini', sc_loc_ini ) 
    295            CALL iom_get( numror, jpdom_autoglo, 'hcssh_loc_ini', hcssh_loc_ini ) 
    296            CALL iom_get( numror, jpdom_autoglo, 'scssh_loc_ini', scssh_loc_ini ) 
     305           IF( .NOT. lk_vvl ) THEN 
     306              CALL iom_get( numror, jpdom_autoglo, 'ssh_hc_loc_ini', ssh_hc_loc_ini ) 
     307              CALL iom_get( numror, jpdom_autoglo, 'ssh_sc_loc_ini', ssh_sc_loc_ini ) 
     308           ENDIF 
    297309       ELSE 
     310          IF(lwp) WRITE(numout,*) '~~~~~~~' 
     311          IF(lwp) WRITE(numout,*) ' dia_hsb at initial state ' 
     312          IF(lwp) WRITE(numout,*) '~~~~~~~' 
    298313          ssh_ini(:,:) = sshn(:,:)                                       ! initial ssh 
    299314          DO jk = 1, jpk 
     
    302317             sc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_sal) * fse3t_n(:,:,jk)   ! initial salt content 
    303318          END DO 
    304           hcssh_loc_ini(:,:) = tsn(:,:,1,jp_tem) * sshn(:,:)   ! initial heat content in ssh 
    305           scssh_loc_ini(:,:) = tsn(:,:,1,jp_sal) * sshn(:,:)   ! initial salt content in ssh 
    306           frc_v = 0._wp                                            
    307           frc_t = 0._wp                                            
    308           frc_s = 0._wp                                                   
     319          frc_v = 0.d0                                           ! volume       trend due to forcing 
     320          frc_t = 0.d0                                           ! heat content   -    -   -    -    
     321          frc_s = 0.d0                                           ! salt content   -    -   -    -         
     322          IF( .NOT. lk_vvl ) THEN 
     323             ssh_hc_loc_ini(:,:) = tsn(:,:,1,jp_tem) * sshn(:,:)   ! initial heat content in ssh 
     324             ssh_sc_loc_ini(:,:) = tsn(:,:,1,jp_sal) * sshn(:,:)   ! initial salt content in ssh 
     325             frc_wn_t = 0.d0                                       ! initial heat content misfit due to free surface 
     326             frc_wn_s = 0.d0                                       ! initial salt content misfit due to free surface 
     327          ENDIF 
    309328       ENDIF 
    310329 
    311330     ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file 
    312331        !                                   ! ------------------- 
    313         IF(lwp) WRITE(numout,*) '---- dia-rst ----' 
     332        IF(lwp) WRITE(numout,*) '~~~~~~~' 
     333        IF(lwp) WRITE(numout,*) ' dia_hsb_rst at it= ', kt,' date= ', ndastp 
     334        IF(lwp) WRITE(numout,*) '~~~~~~~' 
     335 
    314336        CALL iom_rstput( kt, nitrst, numrow, 'frc_v'   , frc_v     ) 
    315337        CALL iom_rstput( kt, nitrst, numrow, 'frc_t'   , frc_t     ) 
    316338        CALL iom_rstput( kt, nitrst, numrow, 'frc_s'   , frc_s     ) 
    317          
     339        IF( .NOT. lk_vvl ) THEN 
     340           CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_t', frc_wn_t ) 
     341           CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_s', frc_wn_s ) 
     342        ENDIF 
    318343        CALL iom_rstput( kt, nitrst, numrow, 'ssh_ini', ssh_ini ) 
    319344        CALL iom_rstput( kt, nitrst, numrow, 'e3t_ini', e3t_ini ) 
    320345        CALL iom_rstput( kt, nitrst, numrow, 'hc_loc_ini', hc_loc_ini ) 
    321346        CALL iom_rstput( kt, nitrst, numrow, 'sc_loc_ini', sc_loc_ini ) 
    322         CALL iom_rstput( kt, nitrst, numrow, 'hcssh_loc_ini', hcssh_loc_ini ) 
    323         CALL iom_rstput( kt, nitrst, numrow, 'scssh_loc_ini', scssh_loc_ini ) 
     347        IF( .NOT. lk_vvl ) THEN 
     348           CALL iom_rstput( kt, nitrst, numrow, 'ssh_hc_loc_ini', ssh_hc_loc_ini ) 
     349           CALL iom_rstput( kt, nitrst, numrow, 'ssh_sc_loc_ini', ssh_sc_loc_ini ) 
     350        ENDIF 
    324351        ! 
    325352     ENDIF 
Note: See TracChangeset for help on using the changeset viewer.