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 6069 for branches/2015/dev_merge_2015/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90 – NEMO

Ignore:
Timestamp:
2015-12-16T16:44:35+01:00 (8 years ago)
Author:
timgraham
Message:

Merge of dev_MetOffice_merge_2015 into branch (only NEMO directory for now).

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_merge_2015/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90

    r6060 r6069  
    4646   REAL(wp) ::   frc_wn_t, frc_wn_s    ! global forcing trends 
    4747   ! 
    48    REAL(wp), DIMENSION(:,:)  , ALLOCATABLE ::   surf          , ssh_ini          ! 
     48   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE ::   surf  
     49   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE ::   surf_ini      , ssh_ini          ! 
    4950   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE ::   ssh_hc_loc_ini, ssh_sc_loc_ini   ! 
    5051   REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   hc_loc_ini, sc_loc_ini, e3t_ini  ! 
     
    99100      IF( ln_rnf_sal)   z_frc_trd_s = z_frc_trd_s + glob_sum( rnf_tsc(:,:,jp_sal) * surf(:,:) ) 
    100101      ! Add ice shelf heat & salt input 
    101       IF( nn_isf .GE. 1 )  THEN 
    102           z_frc_trd_t = z_frc_trd_t + glob_sum( risf_tsc(:,:,jp_tem) * surf(:,:) ) 
    103           z_frc_trd_s = z_frc_trd_s + glob_sum( risf_tsc(:,:,jp_sal) * surf(:,:) ) 
    104       ENDIF 
    105  
     102      IF( ln_isf    ) z_frc_trd_t = z_frc_trd_t + glob_sum( risf_tsc(:,:,jp_tem) * surf(:,:) ) 
    106103      ! Add penetrative solar radiation 
    107104      IF( ln_traqsr )   z_frc_trd_t = z_frc_trd_t + r1_rau0_rcp * glob_sum( qsr     (:,:) * surf(:,:) ) 
     
    137134      ! 2 -  Content variations ! 
    138135      ! ------------------------ ! 
     136      ! glob_sum_full is needed because you keep the full interior domain to compute the sum (iscpl) 
    139137      zdiff_v2 = 0._wp 
    140138      zdiff_hc = 0._wp 
     
    142140 
    143141      ! volume variation (calculated with ssh) 
    144       zdiff_v1 = glob_sum( surf(:,:) * ( sshn(:,:) - ssh_ini(:,:) ) ) 
     142      zdiff_v1 = glob_sum_full( surf(:,:) * sshn(:,:) - surf_ini(:,:) * ssh_ini(:,:) ) 
    145143 
    146144      ! heat & salt content variation (associated with ssh) 
     
    157155            z2d1(:,:) = surf(:,:) * ( tsn(:,:,1,jp_sal) * sshn(:,:) - ssh_sc_loc_ini(:,:) )  
    158156         END IF 
    159          z_ssh_hc = glob_sum( z2d0 )  
    160          z_ssh_sc = glob_sum( z2d1 )  
     157         z_ssh_hc = glob_sum_full( z2d0 )  
     158         z_ssh_sc = glob_sum_full( z2d1 )  
    161159      ENDIF 
    162160 
    163161      DO jk = 1, jpkm1 
    164162         ! volume variation (calculated with scale factors) 
    165          zdiff_v2 = zdiff_v2 + glob_sum( surf(:,:) * tmask(:,:,jk)            & 
    166             &                           * ( e3t_n(:,:,jk) - e3t_ini(:,:,jk) ) ) 
     163         zdiff_v2 = zdiff_v2 + glob_sum_full( surf(:,:) * tmask(:,:,jk)            & 
     164            &                           * e3t_n(:,:,jk) - surf_ini(:,:) * e3t_ini(:,:,jk) ) 
    167165         ! heat content variation 
    168          zdiff_hc = zdiff_hc + glob_sum(  surf(:,:) * tmask(:,:,jk)                                   &  
    169             &                           * ( e3t_n(:,:,jk) * tsn(:,:,jk,jp_tem) - hc_loc_ini(:,:,jk) ) ) 
     166         zdiff_hc = zdiff_hc + glob_sum_full(  surf(:,:) * tmask(:,:,jk)                                   &  
     167            &                           * e3t_n(:,:,jk) * tsn(:,:,jk,jp_tem) - surf_ini(:,:) * hc_loc_ini(:,:,jk) ) ) 
    170168         ! salt content variation 
    171          zdiff_sc = zdiff_sc + glob_sum(  surf(:,:) * tmask(:,:,jk)                                   & 
    172             &                           * ( e3t_n(:,:,jk) * tsn(:,:,jk,jp_sal) - sc_loc_ini(:,:,jk) ) ) 
    173       END DO 
     169         zdiff_sc = zdiff_sc + glob_sum_full( surf    (:,:) * tmask(:,:,jk)                           & 
     170                                        * e3t_n(:,:,jk) * tsn(:,:,jk,jp_sal) - surf_ini(:,:) * sc_loc_ini(:,:,jk) ) 
     171      ENDDO 
    174172 
    175173      ! Substract forcing from heat content, salt content and volume variations 
     
    190188      zvol_tot = 0._wp                    ! total ocean volume (calculated with scale factors) 
    191189      DO jk = 1, jpkm1 
    192          zvol_tot  = zvol_tot + glob_sum( surf(:,:) * tmask(:,:,jk) * e3t_n(:,:,jk) ) 
     190         zvol_tot  = zvol_tot + glob_sum_full( surf(:,:) * tmask(:,:,jk) * e3t_n(:,:,jk) ) 
    193191      END DO 
    194192 
     
    203201        CALL iom_put( 'bgsaline' , zdiff_sc1 / zvol_tot)              ! Salt content variation (psu) 
    204202        CALL iom_put( 'bgheatco' , zdiff_hc1 * 1.e-20 * rau0 * rcp )  ! Heat content variation (1.e20 J)  
    205         CALL iom_put( 'bgsaltco' , zdiff_sc1 * 1.e-9    )             ! Salt content variation (psu*km3) 
    206         CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9    )              ! volume ssh variation (km3)   
     203        CALL iom_put( 'bgsaltco' , zdiff_sc1 * 1.e-9   )              ! Salt content variation (psu*km3) 
     204        CALL iom_put( 'bgvolssh' , zdiff_v1  * 1.e-9   )              ! volume ssh variation (km3)   
    207205        CALL iom_put( 'bgfrcvol' , frc_v    * 1.e-9    )              ! vol - surface forcing (km3)  
    208206        CALL iom_put( 'bgfrctem' , frc_t / zvol_tot    )              ! hc  - surface forcing (C)  
     
    260258              CALL iom_get( numror, 'frc_wn_s', frc_wn_s ) 
    261259           ENDIF 
     260           CALL iom_get( numror, jpdom_autoglo, 'surf_ini', surf_ini ) ! ice sheet coupling 
    262261           CALL iom_get( numror, jpdom_autoglo, 'ssh_ini', ssh_ini ) 
    263262           CALL iom_get( numror, jpdom_autoglo, 'e3t_ini', e3t_ini ) 
     
    272271          IF(lwp) WRITE(numout,*) ' dia_hsb at initial state ' 
    273272          IF(lwp) WRITE(numout,*) '~~~~~~~' 
    274           ssh_ini(:,:) = sshn(:,:)                                       ! initial ssh 
     273          surf_ini(:,:) = e1e2t(:,:) * tmask_i(:,:)         ! initial ocean surface 
     274          ssh_ini(:,:) = sshn(:,:)                          ! initial ssh 
    275275          DO jk = 1, jpk 
    276              e3t_ini   (:,:,jk) = e3t_n(:,:,jk)                        ! initial vertical scale factors 
    277              hc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_tem) * e3t_n(:,:,jk)   ! initial heat content 
    278              sc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_sal) * e3t_n(:,:,jk)   ! initial salt content 
     276             ! if ice sheet/oceqn coupling, need to mask ini variables here (mask could change at the next NEMO instance). 
     277             e3t_ini   (:,:,jk) = e3t_n(:,:,jk)                      * tmask(:,:,jk)  ! initial vertical scale factors 
     278             hc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_tem) * e3t_n(:,:,jk) * tmask(:,:,jk)  ! initial heat content 
     279             sc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_sal) * e3t_n(:,:,jk) * tmask(:,:,jk)  ! initial salt content 
    279280          END DO 
    280281          frc_v = 0._wp                                           ! volume       trend due to forcing 
     
    311312           CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_s', frc_wn_s ) 
    312313        ENDIF 
     314        CALL iom_rstput( kt, nitrst, numrow, 'surf_ini', surf_ini )      ! ice sheet coupling 
    313315        CALL iom_rstput( kt, nitrst, numrow, 'ssh_ini', ssh_ini ) 
    314316        CALL iom_rstput( kt, nitrst, numrow, 'e3t_ini', e3t_ini ) 
     
    378380      ! 1 - Allocate memory ! 
    379381      ! ------------------- ! 
    380       ALLOCATE( hc_loc_ini(jpi,jpj,jpk), sc_loc_ini(jpi,jpj,jpk), & 
    381          &      e3t_ini(jpi,jpj,jpk), surf(jpi,jpj),  ssh_ini(jpi,jpj), STAT=ierror ) 
     382      ALLOCATE( hc_loc_ini(jpi,jpj,jpk), sc_loc_ini(jpi,jpj,jpk), surf_ini(jpi,jpj), & 
     383         &      e3t_ini(jpi,jpj,jpk), surf(jpi,jpj),  ssh_ini(jpi,jpj), STAT=ierror  ) 
    382384      IF( ierror > 0 ) THEN 
    383385         CALL ctl_stop( 'dia_hsb: unable to allocate hc_loc_ini' )   ;   RETURN 
Note: See TracChangeset for help on using the changeset viewer.