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 10696 – NEMO

Changeset 10696


Ignore:
Timestamp:
2019-02-19T13:22:48+01:00 (5 years ago)
Author:
mathiot
Message:

move extended array tt_e,uo_e (...) initialisation to 0. in icbini.F90 and chnage hicth name to hi_e

Location:
NEMO/branches/2019/fix_ticket2238_solution1/src/OCE/ICB
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/fix_ticket2238_solution1/src/OCE/ICB/icb_oce.F90

    r10425 r10696  
    8686   ! particularly for MPP when iceberg can lie inside T grid but outside U, V, or f grid 
    8787   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   uo_e, vo_e 
    88    REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   ff_e, tt_e, fr_e, hicth 
     88   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   ff_e, tt_e, fr_e, hi_e 
    8989   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   ua_e, va_e 
    9090   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   ssh_e 
     
    177177         &      ff_e(0:jpi+1,0:jpj+1) , fr_e(0:jpi+1,0:jpj+1)  ,   & 
    178178         &      tt_e(0:jpi+1,0:jpj+1) , ssh_e(0:jpi+1,0:jpj+1) ,   & 
    179          &      hicth(0:jpi+1,0:jpj+1),                            & 
     179         &      hi_e(0:jpi+1,0:jpj+1) ,                            & 
    180180         &      first_width(nclasses) , first_length(nclasses) ,   & 
    181181         &      src_calving (jpi,jpj) ,                            & 
  • NEMO/branches/2019/fix_ticket2238_solution1/src/OCE/ICB/icbini.F90

    r10570 r10696  
    7474      !                          ! allocate gridded fields 
    7575      IF( icb_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'icb_alloc : unable to allocate arrays' ) 
    76  
     76      ! 
     77      !                          ! initialised variable with extra haloes to zero 
     78      uo_e(:,:) = 0._wp   ;   vo_e(:,:) = 0._wp   ; 
     79      ua_e(:,:) = 0._wp   ;   va_e(:,:) = 0._wp   ; 
     80      ff_e(:,:) = 0._wp   ;   tt_e(:,:) = 0._wp   ; 
     81      fr_e(:,:) = 0._wp   ;   hi_e(:,:) = 0._wp   ; 
     82      ui_e(:,:) = 0._wp   ;   vi_e(:,:) = 0._wp   ; 
     83      ssh_e(:,:) = 0._wp  ;  
     84      ! 
    7785      !                          ! open ascii output file or files for iceberg status information 
    7886      !                          ! note that we choose to do this on all processors since we cannot 
  • NEMO/branches/2019/fix_ticket2238_solution1/src/OCE/ICB/icbutl.F90

    r10695 r10696  
    7070      ! and ssh which is used to calculate gradients 
    7171 
    72       uo_e(:,:) = 0._wp   ;   uo_e(1:jpi,1:jpj) = ssu_m(:,:) * umask(:,:,1) 
    73       vo_e(:,:) = 0._wp   ;   vo_e(1:jpi,1:jpj) = ssv_m(:,:) * vmask(:,:,1) 
    74       ff_e(:,:) = 0._wp   ;   ff_e(1:jpi,1:jpj) = ff_f (:,:)  
    75       tt_e(:,:) = 0._wp   ;   tt_e(1:jpi,1:jpj) = sst_m(:,:) 
    76       fr_e(:,:) = 0._wp   ;   fr_e(1:jpi,1:jpj) = fr_i (:,:) 
    77       ua_e(:,:) = 0._wp   ;   ua_e(1:jpi,1:jpj) = utau (:,:) * umask(:,:,1) ! maybe mask useless because mask applied in sbcblk 
    78       va_e(:,:) = 0._wp   ;   va_e(1:jpi,1:jpj) = vtau (:,:) * vmask(:,:,1) ! maybe mask useless because mask applied in sbcblk 
     72      uo_e(1:jpi,1:jpj) = ssu_m(:,:) * umask(:,:,1) 
     73      vo_e(1:jpi,1:jpj) = ssv_m(:,:) * vmask(:,:,1) 
     74      ff_e(1:jpi,1:jpj) = ff_f (:,:)  
     75      tt_e(1:jpi,1:jpj) = sst_m(:,:) 
     76      fr_e(1:jpi,1:jpj) = fr_i (:,:) 
     77      ua_e(1:jpi,1:jpj) = utau (:,:) * umask(:,:,1) ! maybe mask useless because mask applied in sbcblk 
     78      va_e(1:jpi,1:jpj) = vtau (:,:) * vmask(:,:,1) ! maybe mask useless because mask applied in sbcblk 
    7979      ! 
    8080      CALL lbc_lnk_icb( 'icbutl', uo_e, 'U', -1._wp, 1, 1 ) 
     
    8686      CALL lbc_lnk_icb( 'icbutl', tt_e, 'T', +1._wp, 1, 1 ) 
    8787#if defined key_si3 
    88       hicth(:,:) = 0._wp ;  hicth(1:jpi,1:jpj) = hm_i (:,:)   
    89       ui_e(:,:) = 0._wp ;   ui_e(1:jpi, 1:jpj) = u_ice(:,:) 
    90       vi_e(:,:) = 0._wp ;   vi_e(1:jpi, 1:jpj) = v_ice(:,:) 
     88      hi_e(1:jpi, 1:jpj) = hm_i (:,:)   
     89      ui_e(1:jpi, 1:jpj) = u_ice(:,:) 
     90      vi_e(1:jpi, 1:jpj) = v_ice(:,:) 
    9191      !       
    9292      ! compute ssh slope using ssh_lead if embedded 
    9393      zssh_lead_m(:,:) = ice_var_sshdyn(ssh_m, snwice_mass, snwice_mass_b) 
    94       ssh_e(:,:) = 0._wp ;  ssh_e(1:jpi, 1:jpj) = zssh_lead_m(:,:) * tmask(:,:,1) 
    95       ! 
    96       CALL lbc_lnk_icb( 'icbutl', hicth, 'T', +1._wp, 1, 1 ) 
     94      ssh_e(1:jpi, 1:jpj) = zssh_lead_m(:,:) * tmask(:,:,1) 
     95      ! 
     96      CALL lbc_lnk_icb( 'icbutl', hi_e , 'T', +1._wp, 1, 1 ) 
    9797      CALL lbc_lnk_icb( 'icbutl', ui_e , 'U', -1._wp, 1, 1 ) 
    9898      CALL lbc_lnk_icb( 'icbutl', vi_e , 'V', -1._wp, 1, 1 ) 
    9999#else 
    100       ssh_e(:,:) = 0._wp ;  ssh_e(1:jpi, 1:jpj) = ssh_m(:,:) * tmask(:,:,1) 
     100      ssh_e(1:jpi, 1:jpj) = ssh_m(:,:) * tmask(:,:,1) 
    101101#endif 
    102102      CALL lbc_lnk_icb( 'icbutl', ssh_e, 'T', +1._wp, 1, 1 ) 
     
    150150      pui = icb_utl_bilin_h( ui_e , pi, pj, 'U' )              ! sea-ice velocities 
    151151      pvi = icb_utl_bilin_h( vi_e , pi, pj, 'V' ) 
    152       phi = icb_utl_bilin_h( hicth, pi, pj, 'T' )              ! ice thickness 
     152      phi = icb_utl_bilin_h( hi_e , pi, pj, 'T' )              ! ice thickness 
    153153#else 
    154154      pui = 0._wp 
Note: See TracChangeset for help on using the changeset viewer.