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 3938 for branches/2013/dev_r3406_CNRS_LIM3/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90 – NEMO

Ignore:
Timestamp:
2013-06-26T09:54:16+02:00 (11 years ago)
Author:
flavoni
Message:

dev_r3406_CNRS_LIM3: update LIM3, see ticket #1116

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_r3406_CNRS_LIM3/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90

    r3294 r3938  
    55   !!====================================================================== 
    66   !! History :  3.3  ! 2010-09  (M. Leclair)  Original code  
     7   !!                 ! 2012-10  (C. Rousset)  add iom_put 
    78   !!---------------------------------------------------------------------- 
    89 
     
    2122   USE bdy_par         ! (for lk_bdy) 
    2223   USE timing          ! preformance summary 
     24   USE iom             ! I/O manager 
     25   USE lib_fortran     ! glob_sum 
     26   USE restart         ! ocean restart 
     27   USE wrk_nemo         ! work arrays 
    2328 
    2429   IMPLICIT NONE 
     
    2631 
    2732   PUBLIC   dia_hsb        ! routine called by step.F90 
    28    PUBLIC   dia_hsb_init   ! routine called by opa.F90 
     33   PUBLIC   dia_hsb_init   ! routine called by nemogcm.F90 
     34   PUBLIC   dia_hsb_rst    ! routine called by step.F90 
    2935 
    3036   LOGICAL, PUBLIC ::   ln_diahsb  = .FALSE.   !: check the heat and salt budgets 
    3137 
    32    INTEGER                                 ::   numhsb                           ! 
    33    REAL(dp)                                ::   surf_tot   , vol_tot             ! 
    34    REAL(dp)                                ::   frc_t      , frc_s     , frc_v   ! global forcing trends 
    35    REAL(dp)                                ::   fact1                            ! conversion factors 
    36    REAL(dp)                                ::   fact21    , fact22               !     -         - 
    37    REAL(dp)                                ::   fact31    , fact32               !     -         - 
    38    REAL(dp), DIMENSION(:,:)  , ALLOCATABLE ::   surf      , ssh_ini              ! 
    39    REAL(dp), DIMENSION(:,:,:), ALLOCATABLE ::   hc_loc_ini, sc_loc_ini, e3t_ini  ! 
     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     ! 
    4042 
    4143   !! * Substitutions 
     
    6163      !!             - Compute the contribution of forcing and remove it from these deviations 
    6264      !! 
    63       !! ** Action : Write the results in the 'heat_salt_volume_budgets.txt' ASCII file 
    6465      !!--------------------------------------------------------------------------- 
    6566      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
    6667      !! 
    6768      INTEGER    ::   jk                          ! dummy loop indice 
    68       REAL(dp)   ::   zdiff_hc    , zdiff_sc      ! heat and salt content variations 
    69       REAL(dp)   ::   zdiff_v1    , zdiff_v2      ! volume variation 
    70       REAL(dp)   ::   z1_rau0                     ! local scalars 
    71       REAL(dp)   ::   zdeltat                     !    -     - 
    72       REAL(dp)   ::   z_frc_trd_t , z_frc_trd_s   !    -     - 
    73       REAL(dp)   ::   z_frc_trd_v                 !    -     - 
    74       !!--------------------------------------------------------------------------- 
    75       IF( nn_timing == 1 )   CALL timing_start('dia_hsb') 
    76  
     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)   ::   z1_rau0                     ! local scalars 
     74      REAL(wp)   ::   zdeltat                     !    -     - 
     75      REAL(wp)   ::   z_frc_trd_t , z_frc_trd_s   !    -     - 
     76      REAL(wp)   ::   z_frc_trd_v                 !    -     - 
     77      REAL(wp), POINTER, DIMENSION(:,:)   ::   zsurf              ! 
     78      !!--------------------------------------------------------------------------- 
     79      IF( nn_timing == 1 )   CALL timing_start('dia_hsb')       
     80 
     81      CALL wrk_alloc( jpi, jpj, zsurf ) 
     82   
     83      zsurf(:,:) = e1t(:,:) * e2t(:,:) * tmask(:,:,1) * tmask_i(:,:)      ! masked surface grid cell area 
     84       
    7785      ! ------------------------- ! 
    7886      ! 1 - Trends due to forcing ! 
    7987      ! ------------------------- ! 
    8088      z1_rau0 = 1.e0 / rau0 
    81       z_frc_trd_v = z1_rau0 * SUM( - ( emp(:,:) - rnf(:,:) ) * surf(:,:) )    ! volume fluxes 
    82       z_frc_trd_t =           SUM( sbc_tsc(:,:,jp_tem) * surf(:,:) )     ! heat fluxes 
    83       z_frc_trd_s =           SUM( sbc_tsc(:,:,jp_sal) * surf(:,:) )     ! salt fluxes 
     89      z_frc_trd_v = z1_rau0 * glob_sum( - ( emp(:,:) - rnf(:,:) ) * zsurf(:,:) ) ! volume fluxes 
     90      z_frc_trd_t =           glob_sum( sbc_tsc(:,:,jp_tem) * zsurf(:,:) )       ! heat fluxes 
     91      z_frc_trd_s =           glob_sum( sbc_tsc(:,:,jp_sal) * zsurf(:,:) )       ! salt fluxes 
    8492      ! Add penetrative solar radiation 
    85       IF( ln_traqsr )   z_frc_trd_t = z_frc_trd_t + ro0cpr * SUM( qsr     (:,:) * surf(:,:) ) 
     93      IF( ln_traqsr )   z_frc_trd_t = z_frc_trd_t + ro0cpr * glob_sum( qsr     (:,:) * zsurf(:,:) ) 
    8694      ! Add geothermal heat flux 
    87       IF( ln_trabbc )   z_frc_trd_t = z_frc_trd_t + ro0cpr * SUM( qgh_trd0(:,:) * surf(:,:) ) 
    88       IF( lk_mpp ) THEN 
    89          CALL mpp_sum( z_frc_trd_v ) 
    90          CALL mpp_sum( z_frc_trd_t ) 
    91       ENDIF 
     95      IF( ln_trabbc )   z_frc_trd_t = z_frc_trd_t + ro0cpr * glob_sum( qgh_trd0(:,:) * zsurf(:,:) ) 
     96      ! 
    9297      frc_v = frc_v + z_frc_trd_v * rdt 
    9398      frc_t = frc_t + z_frc_trd_t * rdt 
    9499      frc_s = frc_s + z_frc_trd_s * rdt 
    95100 
    96       ! ----------------------- ! 
    97       ! 2 -  Content variations ! 
    98       ! ----------------------- ! 
    99       zdiff_v2 = 0.d0 
    100       zdiff_hc = 0.d0 
    101       zdiff_sc = 0.d0 
     101      ! ------------------------ ! 
     102      ! 2a -  Content variations ! 
     103      ! ------------------------ ! 
     104      zdiff_v2 = 0._wp 
     105      zdiff_hc = 0._wp 
     106      zdiff_sc = 0._wp 
    102107      ! volume variation (calculated with ssh) 
    103       zdiff_v1 = SUM( surf(:,:) * tmask(:,:,1) * ( sshn(:,:) - ssh_ini(:,:) ) ) 
     108      zdiff_v1 = glob_sum( zsurf(:,:) * ( sshn(:,:) - ssh_ini(:,:) ) ) 
    104109      DO jk = 1, jpkm1 
    105110         ! volume variation (calculated with scale factors) 
    106          zdiff_v2 = zdiff_v2 + SUM( surf(:,:) * tmask(:,:,jk)   & 
    107             &                       * ( fse3t_n(:,:,jk)         & 
    108             &                           - e3t_ini(:,:,jk) ) ) 
     111         zdiff_v2 = zdiff_v2 + glob_sum( zsurf(:,:) * tmask(:,:,jk) * ( fse3t_n(:,:,jk) - e3t_ini(:,:,jk) ) ) 
    109112         ! heat content variation 
    110          zdiff_hc = zdiff_hc + SUM( surf(:,:) * tmask(:,:,jk)          & 
    111             &                       * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_tem)   & 
     113         zdiff_hc = zdiff_hc + glob_sum( zsurf(:,:) * tmask(:,:,jk) * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_tem)   & 
    112114            &                           - hc_loc_ini(:,:,jk) ) ) 
    113115         ! salt content variation 
    114          zdiff_sc = zdiff_sc + SUM( surf(:,:) * tmask(:,:,jk)          & 
    115             &                       * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_sal)   & 
     116         zdiff_sc = zdiff_sc + glob_sum( zsurf(:,:) * tmask(:,:,jk) * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_sal)   & 
    116117            &                           - sc_loc_ini(:,:,jk) ) ) 
    117118      ENDDO 
    118119 
    119       IF( lk_mpp ) THEN 
    120          CALL mpp_sum( zdiff_hc ) 
    121          CALL mpp_sum( zdiff_sc ) 
    122          CALL mpp_sum( zdiff_v1 ) 
    123          CALL mpp_sum( zdiff_v2 ) 
    124       ENDIF 
    125  
    126120      ! Substract forcing from heat content, salt content and volume variations 
    127       zdiff_v1 = zdiff_v1 - frc_v 
    128       zdiff_v2 = zdiff_v2 - frc_v 
    129       zdiff_hc = zdiff_hc - frc_t 
    130       zdiff_sc = zdiff_sc - frc_s 
     121      !frc_v = zdiff_v2 - frc_v 
     122      !frc_t = zdiff_hc - frc_t 
     123      !frc_s = zdiff_sc - frc_s 
    131124       
     125      ! add ssh if not vvl 
     126#ifndef key_vvl 
     127     zdiff_v2 = zdiff_v2 + zdiff_v1 
     128     zdiff_hc = zdiff_hc + glob_sum( zsurf(:,:) * ( sshn(:,:) * tsn(:,:,1,jp_tem)   & 
     129            &                           - hcssh_loc_ini(:,:) ) ) 
     130     zdiff_sc = zdiff_sc + glob_sum( zsurf(:,:) * ( sshn(:,:) * tsn(:,:,1,jp_sal)   & 
     131            &                           - scssh_loc_ini(:,:) ) ) 
     132#endif  
     133      ! 
     134      ! ----------------------- ! 
     135      ! 2b -  Content           ! 
     136      ! ----------------------- ! 
     137      z_v2 = 0._wp 
     138      z_hc = 0._wp 
     139      z_sc = 0._wp 
     140      ! volume (calculated with ssh) 
     141      z_v1 = glob_sum( zsurf(:,:) * sshn(:,:) ) 
     142      DO jk = 1, jpkm1 
     143         ! volume (calculated with scale factors) 
     144         z_v2 = z_v2 + glob_sum( zsurf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) ) 
     145         ! heat content 
     146         z_hc = z_hc + glob_sum( zsurf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) * tsn(:,:,jk,jp_tem) ) 
     147         ! salt content 
     148         z_sc = z_sc + glob_sum( zsurf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) * tsn(:,:,jk,jp_sal) ) 
     149      ENDDO 
     150      ! add ssh if not vvl 
     151#ifndef key_vvl 
     152     z_v2 = z_v2 + z_v1 
     153     z_hc = z_hc + glob_sum( zsurf(:,:) * sshn(:,:) * tsn(:,:,1,jp_tem) ) 
     154     z_sc = z_sc + glob_sum( zsurf(:,:) * sshn(:,:) * tsn(:,:,1,jp_sal) ) 
     155#endif  
     156 
    132157      ! ----------------------- ! 
    133158      ! 3 - Diagnostics writing ! 
    134159      ! ----------------------- ! 
    135160      zdeltat  = 1.e0 / ( ( kt - nit000 + 1 ) * rdt ) 
    136       WRITE(numhsb , 9020) kt , zdiff_hc / vol_tot , zdiff_hc * fact1  * zdeltat,                                & 
    137          &                      zdiff_sc / vol_tot , zdiff_sc * fact21 * zdeltat, zdiff_sc * fact22 * zdeltat,   & 
    138          &                      zdiff_v1           , zdiff_v1 * fact31 * zdeltat, zdiff_v1 * fact32 * zdeltat,   & 
    139          &                      zdiff_v2           , zdiff_v2 * fact31 * zdeltat, zdiff_v2 * fact32 * zdeltat 
    140  
    141       IF ( kt == nitend ) CLOSE( numhsb ) 
    142  
     161! 
     162      CALL iom_put( 'bgtemper',z_hc / z_v2 )               ! Temperature (C)  
     163      CALL iom_put( 'bgsaline',z_sc / z_v2 )               ! Salinity (psu) 
     164      !CALL iom_put( 'bgheatco',zdiff_hc*fact1*zdeltat )      ! Equivalent heat flux (W/m2) 
     165      !CALL iom_put( 'bgsaltco',zdiff_sc*fact21*zdeltat )     ! Equivalent water flux (mm/s) 
     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      ! 
    143177      IF( nn_timing == 1 )   CALL timing_stop('dia_hsb') 
    144  
    145 9020  FORMAT(I5,11D15.7) 
    146       ! 
     178! 
    147179   END SUBROUTINE dia_hsb 
    148180 
     
    160192      !!             - Compute coefficients for conversion 
    161193      !!--------------------------------------------------------------------------- 
    162       CHARACTER (len=32) ::   cl_name  ! output file name 
    163194      INTEGER            ::   jk       ! dummy loop indice 
    164195      INTEGER            ::   ierror   ! local integer 
     
    180211      IF( .NOT. ln_diahsb )   RETURN 
    181212 
    182       ! ------------------- ! 
    183       ! 1 - Allocate memory ! 
    184       ! ------------------- ! 
    185       ALLOCATE( hc_loc_ini(jpi,jpj,jpk), STAT=ierror ) 
    186       IF( ierror > 0 ) THEN 
    187          CALL ctl_stop( 'dia_hsb: unable to allocate hc_loc_ini' )   ;   RETURN 
    188       ENDIF 
    189       ALLOCATE( sc_loc_ini(jpi,jpj,jpk), STAT=ierror ) 
    190       IF( ierror > 0 ) THEN 
    191          CALL ctl_stop( 'dia_hsb: unable to allocate sc_loc_ini' )   ;   RETURN 
    192       ENDIF 
    193       ALLOCATE( e3t_ini(jpi,jpj,jpk)   , STAT=ierror ) 
    194       IF( ierror > 0 ) THEN 
    195          CALL ctl_stop( 'dia_hsb: unable to allocate e3t_ini' )      ;   RETURN 
    196       ENDIF 
    197       ALLOCATE( surf(jpi,jpj)          , STAT=ierror ) 
    198       IF( ierror > 0 ) THEN 
    199          CALL ctl_stop( 'dia_hsb: unable to allocate surf' )         ;   RETURN 
    200       ENDIF 
    201       ALLOCATE( ssh_ini(jpi,jpj)       , STAT=ierror ) 
    202       IF( ierror > 0 ) THEN 
    203          CALL ctl_stop( 'dia_hsb: unable to allocate ssh_ini' )      ;   RETURN 
    204       ENDIF 
    205  
    206       ! ----------------------------------------------- ! 
    207       ! 2 - Time independant variables and file opening ! 
    208       ! ----------------------------------------------- ! 
    209       WRITE(numout,*) "dia_hsb: heat salt volume budgets activated" 
    210       WRITE(numout,*) "~~~~~~~  output written in the 'heat_salt_volume_budgets.txt' ASCII file" 
    211       IF( lk_obc .or. lk_bdy ) THEN 
    212          CALL ctl_warn( 'dia_hsb does not take open boundary fluxes into account' )          
    213       ENDIF 
    214       cl_name    = 'heat_salt_volume_budgets.txt'                         ! name of output file 
    215       surf(:,:) = e1t(:,:) * e2t(:,:) * tmask(:,:,1) * tmask_i(:,:)      ! masked surface grid cell area 
    216       surf_tot  = SUM( surf(:,:) )                                       ! total ocean surface area 
    217       vol_tot   = 0.d0                                                   ! total ocean volume 
    218       DO jk = 1, jpkm1 
    219          vol_tot  = vol_tot + SUM( surf(:,:) * tmask(:,:,jk)     & 
    220             &                      * fse3t_n(:,:,jk)         ) 
    221       END DO 
    222       IF( lk_mpp ) THEN  
    223          CALL mpp_sum( vol_tot ) 
    224          CALL mpp_sum( surf_tot ) 
    225       ENDIF 
    226  
    227       CALL ctl_opn( numhsb , cl_name , 'UNKNOWN' , 'FORMATTED' , 'SEQUENTIAL' , 1 , numout , lwp , 1 ) 
    228       !                   12345678901234567890123456789012345678901234567890123456789012345678901234567890 -> 80 
    229       WRITE( numhsb, 9010 ) "kt   |     heat content budget     |            salt content budget             ",   & 
    230          !                                                   123456789012345678901234567890123456789012345 -> 45 
    231          &                                                  "|            volume budget (ssh)             ",   & 
    232          !                                                   678901234567890123456789012345678901234567890 -> 45 
    233          &                                                  "|            volume budget (e3t)             " 
    234       WRITE( numhsb, 9010 ) "     |      [C]         [W/m2]     |     [psu]        [mmm/s]          [SV]     ",   & 
    235          &                                                  "|     [m3]         [mmm/s]          [SV]     ",   & 
    236          &                                                  "|     [m3]         [mmm/s]          [SV]     " 
    237  
    238       ! --------------- ! 
    239       ! 3 - Conversions ! (factors will be multiplied by duration afterwards) 
    240       ! --------------- ! 
    241  
    242       ! heat content variation   =>   equivalent heat flux: 
    243       fact1  = rau0 * rcp / surf_tot                                         ! [C*m3]   ->  [W/m2] 
    244       ! salt content variation   =>   equivalent EMP and equivalent "flow":  
    245       fact21 = 1.e3  / ( soce * surf_tot )                                   ! [psu*m3] ->  [mm/s] 
    246       fact22 = 1.e-6 / soce                                                  ! [psu*m3] ->  [Sv] 
    247       ! volume variation         =>   equivalent EMP and equivalent "flow": 
    248       fact31 = 1.e3  / surf_tot                                              ! [m3]     ->  [mm/s] 
    249       fact32 = 1.e-6                                                         ! [m3]     ->  [SV] 
    250  
    251       ! ---------------------------------- ! 
    252       ! 4 - initial conservation variables ! 
    253       ! ---------------------------------- ! 
    254       ssh_ini(:,:) = sshn(:,:)                                       ! initial ssh 
    255       DO jk = 1, jpk 
    256          e3t_ini   (:,:,jk) = fse3t_n(:,:,jk)                        ! initial vertical scale factors 
    257          hc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_tem) * fse3t_n(:,:,jk)   ! initial heat content 
    258          sc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_sal) * fse3t_n(:,:,jk)   ! initial salt content 
    259       END DO 
    260       frc_v = 0.d0                                           ! volume       trend due to forcing 
    261       frc_t = 0.d0                                           ! heat content   -    -   -    -    
    262       frc_s = 0.d0                                           ! salt content   -    -   -    -          
    263       ! 
    264 9010  FORMAT(A80,A45,A45) 
     213         ! ------------------- ! 
     214         ! 1 - Allocate memory ! 
     215         ! ------------------- ! 
     216         ALLOCATE( hc_loc_ini(jpi,jpj,jpk), STAT=ierror ) 
     217         IF( ierror > 0 ) THEN 
     218            CALL ctl_stop( 'dia_hsb: unable to allocate hc_loc_ini' )   ;   RETURN 
     219         ENDIF 
     220         ALLOCATE( sc_loc_ini(jpi,jpj,jpk), STAT=ierror ) 
     221         IF( ierror > 0 ) THEN 
     222            CALL ctl_stop( 'dia_hsb: unable to allocate sc_loc_ini' )   ;   RETURN 
     223         ENDIF 
     224         ALLOCATE( hcssh_loc_ini(jpi,jpj), STAT=ierror ) 
     225         IF( ierror > 0 ) THEN 
     226            CALL ctl_stop( 'dia_hsb: unable to allocate hcssh_loc_ini' )   ;   RETURN 
     227         ENDIF 
     228         ALLOCATE( scssh_loc_ini(jpi,jpj), STAT=ierror ) 
     229         IF( ierror > 0 ) THEN 
     230            CALL ctl_stop( 'dia_hsb: unable to allocate scssh_loc_ini' )   ;   RETURN 
     231         ENDIF 
     232         ALLOCATE( e3t_ini(jpi,jpj,jpk)   , STAT=ierror ) 
     233         IF( ierror > 0 ) THEN 
     234            CALL ctl_stop( 'dia_hsb: unable to allocate e3t_ini' )      ;   RETURN 
     235         ENDIF 
     236         ALLOCATE( ssh_ini(jpi,jpj)       , STAT=ierror ) 
     237         IF( ierror > 0 ) THEN 
     238            CALL ctl_stop( 'dia_hsb: unable to allocate ssh_ini' )      ;   RETURN 
     239         ENDIF 
     240          
     241         ! ----------------------------------------------- ! 
     242         ! 2 - Time independant variables and file opening ! 
     243         ! ----------------------------------------------- ! 
     244         WRITE(numout,*) "dia_hsb: heat salt volume budgets activated" 
     245         IF( lk_obc .or. lk_bdy ) THEN 
     246            CALL ctl_warn( 'dia_hsb does not take open boundary fluxes into account' )          
     247         ENDIF 
     248          
     249         ! ---------------------------------- ! 
     250         ! 4 - initial conservation variables ! 
     251         ! ---------------------------------- ! 
     252         !ssh_ini(:,:) = sshn(:,:)                                       ! initial ssh 
     253         !DO jk = 1, jpk 
     254         !   e3t_ini   (:,:,jk) = fse3t_n(:,:,jk)                        ! initial vertical scale factors 
     255         !   hc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_tem) * fse3t_n(:,:,jk)   ! initial heat content 
     256         !   sc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_sal) * fse3t_n(:,:,jk)   ! initial salt content 
     257         !END DO 
     258         !hcssh_loc_ini(:,:) = tsn(:,:,1,jp_tem) * sshn(:,:)   ! initial heat content in ssh 
     259         !scssh_loc_ini(:,:) = tsn(:,:,1,jp_sal) * sshn(:,:)   ! initial salt content in ssh 
     260         !frc_v = 0._wp                                           ! volume       trend due to forcing 
     261         !frc_t = 0._wp                                           ! heat content   -    -   -    -    
     262         !frc_s = 0._wp                                           ! salt content   -    -   -    -          
     263         ! 
     264         CALL dia_hsb_rst( nit000, 'READ' )  !* read or initialize all required files 
    265265      ! 
    266266   END SUBROUTINE dia_hsb_init 
     267 
     268   SUBROUTINE dia_hsb_rst( kt, cdrw ) 
     269     !!--------------------------------------------------------------------- 
     270     !!                   ***  ROUTINE limdia_rst  *** 
     271     !!                      
     272     !! ** Purpose :   Read or write DIA file in restart file 
     273     !! 
     274     !! ** Method  :   use of IOM library 
     275     !!---------------------------------------------------------------------- 
     276     INTEGER         , INTENT(in) ::   kt     ! ocean time-step 
     277     CHARACTER(len=*), INTENT(in) ::   cdrw   ! "READ"/"WRITE" flag 
     278     ! 
     279     INTEGER ::   jk   !  
     280     INTEGER ::   id1   ! local integers 
     281     !!---------------------------------------------------------------------- 
     282     ! 
     283     IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise  
     284        IF( ln_rstart ) THEN                   !* Read the restart file 
     285           !id1 = iom_varid( numror, 'frc_vol'  , ldstop = .FALSE. ) 
     286           ! 
     287           CALL iom_get( numror, 'frc_v', frc_v ) 
     288           CALL iom_get( numror, 'frc_t', frc_t ) 
     289           CALL iom_get( numror, 'frc_s', frc_s ) 
     290 
     291           CALL iom_get( numror, jpdom_autoglo, 'ssh_ini', ssh_ini ) 
     292           CALL iom_get( numror, jpdom_autoglo, 'e3t_ini', e3t_ini ) 
     293           CALL iom_get( numror, jpdom_autoglo, 'hc_loc_ini', hc_loc_ini ) 
     294           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 ) 
     297       ELSE 
     298          ssh_ini(:,:) = sshn(:,:)                                       ! initial ssh 
     299          DO jk = 1, jpk 
     300             e3t_ini   (:,:,jk) = fse3t_n(:,:,jk)                        ! initial vertical scale factors 
     301             hc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_tem) * fse3t_n(:,:,jk)   ! initial heat content 
     302             sc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_sal) * fse3t_n(:,:,jk)   ! initial salt content 
     303          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                                                   
     309       ENDIF    
     310 
     311     ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file 
     312        !                                   ! ------------------- 
     313        IF(lwp) WRITE(numout,*) '---- dia-rst ----' 
     314        CALL iom_rstput( kt, nitrst, numrow, 'frc_v'   , frc_v     ) 
     315        CALL iom_rstput( kt, nitrst, numrow, 'frc_t'   , frc_t     ) 
     316        CALL iom_rstput( kt, nitrst, numrow, 'frc_s'   , frc_s     ) 
     317         
     318        CALL iom_rstput( kt, nitrst, numrow, 'ssh_ini', ssh_ini ) 
     319        CALL iom_rstput( kt, nitrst, numrow, 'e3t_ini', e3t_ini ) 
     320        CALL iom_rstput( kt, nitrst, numrow, 'hc_loc_ini', hc_loc_ini ) 
     321        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 ) 
     324        ! 
     325     ENDIF 
     326     ! 
     327   END SUBROUTINE dia_hsb_rst 
    267328 
    268329   !!====================================================================== 
Note: See TracChangeset for help on using the changeset viewer.