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 5820 for branches/NERC/dev_r5589_is_oce_cpl/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90 – NEMO

Ignore:
Timestamp:
2015-10-21T18:01:58+02:00 (9 years ago)
Author:
mathiot
Message:

ice sheet coupling: remove some print, fix pb in diahsb if ssmask is modified, rm corner extrapolation + some bug fix in conservation option

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/NERC/dev_r5589_is_oce_cpl/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90

    r5802 r5820  
    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  ! 
     
    144145 
    145146      ! volume variation (calculated with ssh) 
    146       zdiff_v1 = glob_sum( surf(:,:) * ( sshn(:,:) - ssh_ini(:,:) ) ) 
     147      zdiff_v1 = glob_sum_full( surf(:,:) * sshn(:,:) - surf_ini(:,:) * ssh_ini(:,:) ) 
    147148 
    148149      ! heat & salt content variation (associated with ssh) 
     
    165166      DO jk = 1, jpkm1 
    166167         ! volume variation (calculated with scale factors) 
    167          zdiff_v2 = zdiff_v2 + glob_sum( surf(:,:) * ( tmask(:,:,jk) & 
    168             &                           * fse3t_n(:,:,jk) - e3t_ini(:,:,jk) ) ) 
    169          ! heat content variation 
    170          zdiff_hc = zdiff_hc + glob_sum(  surf(:,:) * ( tmask(:,:,jk) &  
    171             &                           * 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) ) 
    172173         ! salt content variation 
    173          zdiff_sc = zdiff_sc + glob_sum(  surf(:,:) * ( tmask(:,:,jk)   & 
    174             &                           * 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) ) 
    175176      ENDDO 
    176177 
     
    192193      zvol_tot = 0._wp                    ! total ocean volume (calculated with scale factors) 
    193194      DO jk = 1, jpkm1 
    194          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) ) 
    195196      END DO 
    196197 
     
    268269              CALL iom_get( numror, 'frc_wn_s', frc_wn_s ) 
    269270           ENDIF 
     271           CALL iom_get( numror, jpdom_autoglo, 'surf_ini', surf_ini ) 
    270272           CALL iom_get( numror, jpdom_autoglo, 'ssh_ini', ssh_ini ) 
    271273           CALL iom_get( numror, jpdom_autoglo, 'e3t_ini', e3t_ini ) 
     
    280282          IF(lwp) WRITE(numout,*) ' dia_hsb at initial state ' 
    281283          IF(lwp) WRITE(numout,*) '~~~~~~~' 
     284          surf_ini(:,:) = e1t(:,:) * e2t(:,:) * tmask_i(:,:)             ! initial ocean surface 
    282285          ssh_ini(:,:) = sshn(:,:)                                       ! initial ssh 
    283286          DO jk = 1, jpk 
     
    320323           CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_s', frc_wn_s ) 
    321324        ENDIF 
     325        CALL iom_rstput( kt, nitrst, numrow, 'surf_ini', surf_ini ) 
    322326        CALL iom_rstput( kt, nitrst, numrow, 'ssh_ini', ssh_ini ) 
    323327        CALL iom_rstput( kt, nitrst, numrow, 'e3t_ini', e3t_ini ) 
     
    387391      ! 1 - Allocate memory ! 
    388392      ! ------------------- ! 
    389       ALLOCATE( hc_loc_ini(jpi,jpj,jpk), sc_loc_ini(jpi,jpj,jpk), & 
    390          &      e3t_ini(jpi,jpj,jpk), surf(jpi,jpj),  ssh_ini(jpi,jpj), STAT=ierror ) 
     393      ALLOCATE( hc_loc_ini(jpi,jpj,jpk), sc_loc_ini(jpi,jpj,jpk), surf_ini(jpi,jpj), & 
     394         &      e3t_ini(jpi,jpj,jpk), surf(jpi,jpj),  ssh_ini(jpi,jpj), STAT=ierror  ) 
    391395      IF( ierror > 0 ) THEN 
    392396         CALL ctl_stop( 'dia_hsb: unable to allocate hc_loc_ini' )   ;   RETURN 
Note: See TracChangeset for help on using the changeset viewer.