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

Ignore:
Timestamp:
2013-12-11T18:34:00+01:00 (10 years ago)
Author:
clem
Message:

remove remaining bugs in LIM3, so that it can run in both regional and global config

File:
1 edited

Legend:

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

    r4328 r4333  
    3636   LOGICAL, PUBLIC ::   ln_diahsb   !: check the heat and salt budgets 
    3737 
    38    REAL(dp), SAVE                                ::   frc_t      , frc_s     , frc_v   ! global forcing trends 
    39    REAL(dp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ssh_ini              ! 
    40    REAL(dp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hc_loc_ini, sc_loc_ini, e3t_ini  ! 
    41    REAL(dp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hcssh_loc_ini, scssh_loc_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     ! 
    4242 
    4343   !! * Substitutions 
     
    6767      !! 
    6868      INTEGER    ::   jk                          ! dummy loop indice 
    69       REAL(dp)   ::   zdiff_hc    , zdiff_sc      ! heat and salt content variations 
    70       REAL(dp)   ::   zdiff_v1    , zdiff_v2      ! volume variation 
    71       REAL(dp)   ::   z_hc        , z_sc          ! heat and salt content 
    72       REAL(dp)   ::   z_v1        , z_v2          ! volume 
    73       REAL(dp)   ::   zdeltat                     !    -     - 
    74       REAL(dp)   ::   z_frc_trd_t , z_frc_trd_s   !    -     - 
    75       REAL(dp)   ::   z_frc_trd_v                 !    -     - 
    76       REAL(dp), POINTER, DIMENSION(:,:)   ::   zsurf              ! 
     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              ! 
    7777      !!--------------------------------------------------------------------------- 
    7878      IF( nn_timing == 1 )   CALL timing_start('dia_hsb')       
     
    104104      ! 2a -  Content variations ! 
    105105      ! ------------------------ ! 
    106       zdiff_v2 = 0._dp 
    107       zdiff_hc = 0._dp 
    108       zdiff_sc = 0._dp 
     106      zdiff_v2 = 0._wp 
     107      zdiff_hc = 0._wp 
     108      zdiff_sc = 0._wp 
    109109      ! volume variation (calculated with ssh) 
    110110      zdiff_v1 = glob_sum( zsurf(:,:) * ( sshn(:,:) - ssh_ini(:,:) ) ) 
    111111      DO jk = 1, jpkm1 
    112112         ! volume variation (calculated with scale factors) 
    113          zdiff_v2 = zdiff_v2 & 
    114             &  + glob_sum( zsurf(:,:) * tmask(:,:,jk) * ( fse3t_n(:,:,jk) - e3t_ini(:,:,jk) ) ) 
     113         zdiff_v2 = zdiff_v2 + glob_sum( zsurf(:,:) * tmask(:,:,jk) * ( fse3t_n(:,:,jk) - e3t_ini(:,:,jk) ) ) 
    115114         ! heat content variation 
    116          zdiff_hc = zdiff_hc & 
    117             &  + glob_sum( zsurf(:,:) * tmask(:,:,jk) * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_tem)   & 
     115         zdiff_hc = zdiff_hc + glob_sum( zsurf(:,:) * tmask(:,:,jk) * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_tem)   & 
    118116            &                           - hc_loc_ini(:,:,jk) ) ) 
    119117         ! salt content variation 
    120          zdiff_sc = zdiff_sc & 
    121             &  + glob_sum( zsurf(:,:) * tmask(:,:,jk) * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_sal)   & 
     118         zdiff_sc = zdiff_sc + glob_sum( zsurf(:,:) * tmask(:,:,jk) * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_sal)   & 
    122119            &                           - sc_loc_ini(:,:,jk) ) ) 
    123120      ENDDO 
     
    140137      ! 2b -  Content           ! 
    141138      ! ----------------------- ! 
    142       z_v2 = 0._dp 
    143       z_hc = 0._dp 
    144       z_sc = 0._dp 
     139      z_v2 = 0._wp 
     140      z_hc = 0._wp 
     141      z_sc = 0._wp 
    145142      ! volume (calculated with ssh) 
    146143      z_v1 = glob_sum( zsurf(:,:) * sshn(:,:) ) 
    147144      DO jk = 1, jpkm1 
    148145         ! volume (calculated with scale factors) 
    149          z_v2 = z_v2 & 
    150             &     + glob_sum( zsurf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) ) 
     146         z_v2 = z_v2 + glob_sum( zsurf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) ) 
    151147         ! heat content 
    152          z_hc = z_hc & 
    153             &     + glob_sum( zsurf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) * tsn(:,:,jk,jp_tem) ) 
     148         z_hc = z_hc + glob_sum( zsurf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) * tsn(:,:,jk,jp_tem) ) 
    154149         ! salt content 
    155          z_sc = z_sc & 
    156             &     + glob_sum( zsurf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) * tsn(:,:,jk,jp_sal) ) 
     150         z_sc = z_sc + glob_sum( zsurf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) * tsn(:,:,jk,jp_sal) ) 
    157151      ENDDO 
    158152      ! add ssh if not vvl 
     
    170164      CALL iom_put( 'bgtemper' , z_hc / z_v2 )                      ! Temperature (C)  
    171165      CALL iom_put( 'bgsaline' , z_sc / z_v2 )                      ! Salinity (psu) 
    172       CALL iom_put( 'bgheatco' , zdiff_hc * rau0 * rcp * 1.e-9_dp ) ! Heat content variation (10^9 J) 
     166      CALL iom_put( 'bgheatco' , zdiff_hc * rau0 * rcp * 1.e-9_wp ) ! Heat content variation (10^9 J) 
    173167      CALL iom_put( 'bgsaltco' , zdiff_sc * 1.e-9 )                 ! Salt content variation (psu*km3)  
    174168      CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9 )                    ! volume ssh (km3)   
     
    176170      CALL iom_put( 'bgvoltot' , zdiff_v2 * 1.e-9 )                 ! volume total (km3)  
    177171      CALL iom_put( 'bgfrcvol' , frc_v * 1.e-9 )                     ! vol - surface forcing (volume)  
    178       CALL iom_put( 'bgfrctem' , frc_t * rau0 * rcp * 1.e-9_dp ) ! hc  - surface forcing (heat content)  
     172      CALL iom_put( 'bgfrctem' , frc_t * rau0 * rcp * 1.e-9_wp ) ! hc  - surface forcing (heat content)  
    179173      CALL iom_put( 'bgfrcsal' , frc_s * 1.e-9 )                     ! sc  - surface forcing (salt content)  
    180174      ! 
     
    224218      IF(lwp) THEN                   ! Control print 
    225219         WRITE(numout,*) 
     220         WRITE(numout,*) 'dia_hsb_init : check the heat and salt budgets' 
     221         WRITE(numout,*) '~~~~~~~~~~~~' 
    226222         WRITE(numout,*) '   Namelist namhsb : set hsb parameters' 
    227223         WRITE(numout,*) '      Switch for hsb diagnostic (T) or not (F)  ln_diahsb  = ', ln_diahsb 
     
    308304          hcssh_loc_ini(:,:) = tsn(:,:,1,jp_tem) * sshn(:,:)   ! initial heat content in ssh 
    309305          scssh_loc_ini(:,:) = tsn(:,:,1,jp_sal) * sshn(:,:)   ! initial salt content in ssh 
    310           frc_v = 0._dp                                            
    311           frc_t = 0._dp                                            
    312           frc_s = 0._dp                                                   
     306          frc_v = 0._wp                                            
     307          frc_t = 0._wp                                            
     308          frc_s = 0._wp                                                   
    313309       ENDIF 
    314310 
Note: See TracChangeset for help on using the changeset viewer.