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

Ignore:
Timestamp:
2015-12-04T17:56:07+01:00 (8 years ago)
Author:
mathiot
Message:

Merged ice sheet coupling branch

File:
1 edited

Legend:

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

    r5643 r6006  
    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  ! 
     
    138139      ! 2 -  Content variations ! 
    139140      ! ------------------------ ! 
     141      ! glob_sum_full is needed because you keep the full interior domain to compute the sum (iscpl) 
    140142      zdiff_v2 = 0._wp 
    141143      zdiff_hc = 0._wp 
     
    143145 
    144146      ! volume variation (calculated with ssh) 
    145       zdiff_v1 = glob_sum( surf(:,:) * ( sshn(:,:) - ssh_ini(:,:) ) ) 
     147      zdiff_v1 = glob_sum_full( surf(:,:) * sshn(:,:) - surf_ini(:,:) * ssh_ini(:,:) ) 
    146148 
    147149      ! heat & salt content variation (associated with ssh) 
     
    158160            z2d1(:,:) = surf(:,:) * ( tsn(:,:,1,jp_sal) * sshn(:,:) - ssh_sc_loc_ini(:,:) )  
    159161         END IF 
    160          z_ssh_hc = glob_sum( z2d0 )  
    161          z_ssh_sc = glob_sum( z2d1 )  
     162         z_ssh_hc = glob_sum_full( z2d0 )  
     163         z_ssh_sc = glob_sum_full( z2d1 )  
    162164      ENDIF 
    163165 
    164166      DO jk = 1, jpkm1 
    165167         ! volume variation (calculated with scale factors) 
    166          zdiff_v2 = zdiff_v2 + glob_sum( surf(:,:) * tmask(:,:,jk) & 
    167             &                           * ( fse3t_n(:,:,jk) - e3t_ini(:,:,jk) ) ) 
    168          ! heat content variation 
    169          zdiff_hc = zdiff_hc + glob_sum(  surf(:,:) * tmask(:,:,jk) &  
    170             &                           * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_tem) - hc_loc_ini(:,:,jk) ) ) 
     168         zdiff_v2 = zdiff_v2 + glob_sum_full( surf    (:,:) * fse3t_n  (:,:,jk) * tmask(:,:,jk) & 
     169              &                             - surf_ini(:,:) *   e3t_ini(:,:,jk) ) 
     170         ! heat content variation  
     171         zdiff_hc = zdiff_hc + glob_sum_full( surf    (:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) * tsn(:,:,jk,jp_tem) & 
     172              &                             - surf_ini(:,:) * hc_loc_ini(:,:,jk) ) 
    171173         ! salt content variation 
    172          zdiff_sc = zdiff_sc + glob_sum(  surf(:,:) * tmask(:,:,jk)   & 
    173             &                           * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_sal) - sc_loc_ini(:,:,jk) ) ) 
     174         zdiff_sc = zdiff_sc + glob_sum_full( surf    (:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) * tsn(:,:,jk,jp_sal) &  
     175              &                             - surf_ini(:,:) * sc_loc_ini(:,:,jk) ) 
    174176      ENDDO 
    175177 
     
    191193      zvol_tot = 0._wp                    ! total ocean volume (calculated with scale factors) 
    192194      DO jk = 1, jpkm1 
    193          zvol_tot  = zvol_tot + glob_sum( surf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) ) 
     195         zvol_tot  = zvol_tot + glob_sum_full( surf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) ) 
    194196      END DO 
    195197 
     
    214216        CALL iom_put( 'bgsaline' , zdiff_sc1 / zvol_tot)              ! Salt content variation (psu) 
    215217        CALL iom_put( 'bgheatco' , zdiff_hc1 * 1.e-20 * rau0 * rcp )  ! Heat content variation (1.e20 J)  
    216         CALL iom_put( 'bgsaltco' , zdiff_sc1 * 1.e-9    )             ! Salt content variation (psu*km3) 
    217         CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9    )              ! volume ssh variation (km3)   
     218        CALL iom_put( 'bgsaltco' , zdiff_sc1 * 1.e-9   )              ! Salt content variation (psu*km3) 
     219        CALL iom_put( 'bgvolssh' , zdiff_v1  * 1.e-9   )              ! volume ssh variation (km3)   
    218220        CALL iom_put( 'bgfrcvol' , frc_v    * 1.e-9    )              ! vol - surface forcing (km3)  
    219221        CALL iom_put( 'bgfrctem' , frc_t / zvol_tot    )              ! hc  - surface forcing (C)  
     
    261263              CALL iom_get( numror, 'frc_wn_s', frc_wn_s ) 
    262264           ENDIF 
     265           CALL iom_get( numror, jpdom_autoglo, 'surf_ini', surf_ini ) ! ice sheet coupling 
    263266           CALL iom_get( numror, jpdom_autoglo, 'ssh_ini', ssh_ini ) 
    264267           CALL iom_get( numror, jpdom_autoglo, 'e3t_ini', e3t_ini ) 
     
    273276          IF(lwp) WRITE(numout,*) ' dia_hsb at initial state ' 
    274277          IF(lwp) WRITE(numout,*) '~~~~~~~' 
    275           ssh_ini(:,:) = sshn(:,:)                                       ! initial ssh 
     278          surf_ini(:,:) = e1e2t(:,:) * tmask_i(:,:)         ! initial ocean surface 
     279          ssh_ini(:,:) = sshn(:,:)                          ! initial ssh 
    276280          DO jk = 1, jpk 
    277              e3t_ini   (:,:,jk) = fse3t_n(:,:,jk)                        ! initial vertical scale factors 
    278              hc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_tem) * fse3t_n(:,:,jk)   ! initial heat content 
    279              sc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_sal) * fse3t_n(:,:,jk)   ! initial salt content 
     281             ! if ice sheet/oceqn coupling, need to mask ini variables here (mask could change at the next NEMO instance). 
     282             e3t_ini   (:,:,jk) = fse3t_n(:,:,jk)    * tmask(:,:,jk)                    ! initial vertical scale factors 
     283             hc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_tem) * fse3t_n(:,:,jk) * tmask(:,:,jk)  ! initial heat content 
     284             sc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_sal) * fse3t_n(:,:,jk) * tmask(:,:,jk)  ! initial salt content 
    280285          END DO 
    281286          frc_v = 0._wp                                           ! volume       trend due to forcing 
     
    312317           CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_s', frc_wn_s ) 
    313318        ENDIF 
     319        CALL iom_rstput( kt, nitrst, numrow, 'surf_ini', surf_ini )      ! ice sheet coupling 
    314320        CALL iom_rstput( kt, nitrst, numrow, 'ssh_ini', ssh_ini ) 
    315321        CALL iom_rstput( kt, nitrst, numrow, 'e3t_ini', e3t_ini ) 
     
    379385      ! 1 - Allocate memory ! 
    380386      ! ------------------- ! 
    381       ALLOCATE( hc_loc_ini(jpi,jpj,jpk), sc_loc_ini(jpi,jpj,jpk), & 
    382          &      e3t_ini(jpi,jpj,jpk), surf(jpi,jpj),  ssh_ini(jpi,jpj), STAT=ierror ) 
     387      ALLOCATE( hc_loc_ini(jpi,jpj,jpk), sc_loc_ini(jpi,jpj,jpk), surf_ini(jpi,jpj), & 
     388         &      e3t_ini(jpi,jpj,jpk), surf(jpi,jpj),  ssh_ini(jpi,jpj), STAT=ierror  ) 
    383389      IF( ierror > 0 ) THEN 
    384390         CALL ctl_stop( 'dia_hsb: unable to allocate hc_loc_ini' )   ;   RETURN 
Note: See TracChangeset for help on using the changeset viewer.