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 10701 for NEMO/branches/2019 – NEMO

Changeset 10701 for NEMO/branches/2019


Ignore:
Timestamp:
2019-02-19T20:15:53+01:00 (5 years ago)
Author:
mathiot
Message:

update branch to head of the trunk (ticket #2238)

Location:
NEMO/branches/2019/fix_ticket2238_solution1
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/fix_ticket2238_solution1/cfgs/README.rst

    r10605 r10701  
    235235.. literalinclude:: ../../../cfgs/GYRE_PISCES/EXPREF/namelist_ref 
    236236   :language: fortran 
    237    :lines: 306-333 
     237   :lines: 935-960 
    238238 
    239239Input dynamical fields for this configuration (``ORCA2_OFF_v4.0.tar``) comes from 
  • NEMO/branches/2019/fix_ticket2238_solution1/src/OCE/ICB/icb_oce.F90

    r10700 r10701  
    8989   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   ua_e, va_e 
    9090   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   ssh_e 
     91   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   tmask_e, umask_e, vmask_e 
    9192#if defined key_si3 || defined key_cice 
    9293   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   hi_e, ui_e, vi_e 
     
    169170      ! 
    170171      ! expanded arrays for bilinear interpolation 
    171       ALLOCATE( uo_e(0:jpi+1,0:jpj+1) , ua_e(0:jpi+1,0:jpj+1) ,   & 
    172          &      vo_e(0:jpi+1,0:jpj+1) , va_e(0:jpi+1,0:jpj+1) ,   & 
     172      ALLOCATE( uo_e(0:jpi+1,0:jpj+1) , ua_e(0:jpi+1,0:jpj+1) ,    & 
     173         &      vo_e(0:jpi+1,0:jpj+1) , va_e(0:jpi+1,0:jpj+1) ,    & 
    173174#if defined key_si3 || defined key_cice 
    174175         &      ui_e(0:jpi+1,0:jpj+1) ,                            & 
     
    183184      icb_alloc = icb_alloc + ill 
    184185 
     186      ALLOCATE( tmask_e(0:jpi+1,0:jpj+1), umask_e(0:jpi+1,0:jpj+1), vmask_e(0:jpi+1,0:jpj+1), & 
     187         &      STAT=ill) 
     188      icb_alloc = icb_alloc + ill 
     189 
    185190      ALLOCATE( nicbfldpts(jpi) , nicbflddest(jpi) , nicbfldproc(jpni) , & 
    186191         &      nicbfldnsend(jpni), nicbfldexpect(jpni) , nicbfldreq(jpni), STAT=ill) 
  • NEMO/branches/2019/fix_ticket2238_solution1/src/OCE/ICB/icbini.F90

    r10700 r10701  
    235235      src_calving_hflx(:,:) = 0._wp 
    236236 
     237      ! definition of extended surface masked needed by icb_bilin_h 
     238      tmask_e(:,:) = 0._wp   ;   tmask_e(1:jpi,1:jpj) = tmask(:,:,1) 
     239      umask_e(:,:) = 0._wp   ;   umask_e(1:jpi,1:jpj) = umask(:,:,1) 
     240      vmask_e(:,:) = 0._wp   ;   vmask_e(1:jpi,1:jpj) = vmask(:,:,1) 
     241      CALL lbc_lnk_icb( 'icbini', tmask_e, 'T', +1._wp, 1, 1 ) 
     242      CALL lbc_lnk_icb( 'icbini', umask_e, 'T', +1._wp, 1, 1 ) 
     243      CALL lbc_lnk_icb( 'icbini', vmask_e, 'T', +1._wp, 1, 1 ) 
     244      ! 
    237245      ! assign each new iceberg with a unique number constructed from the processor number 
    238246      ! and incremented by the total number of processors 
  • NEMO/branches/2019/fix_ticket2238_solution1/src/OCE/ICB/icbutl.F90

    r10696 r10701  
    120120      !!             is half the off shore value, wile the normal-to-the-coast value is zero. 
    121121      !!             This is OK as a starting point. 
     122      !!       !!pm  HARD CODED: - rho_air now computed in sbcblk (what are the effect ?) 
     123      !!                         - drag coefficient (should it be namelist parameter ?) 
    122124      !! 
    123125      !!---------------------------------------------------------------------- 
     
    131133      !!---------------------------------------------------------------------- 
    132134 
    133       pe1 = icb_utl_bilin_e( e1t, e1u, e1v, e1f, pi, pj )     ! scale factors 
     135      pe1 = icb_utl_bilin_e( e1t, e1u, e1v, e1f, pi, pj )      ! scale factors 
    134136      pe2 = icb_utl_bilin_e( e2t, e2u, e2v, e2f, pi, pj ) 
    135137      ! 
    136       puo  = icb_utl_bilin_h( uo_e, pi, pj, 'U' )             ! ocean velocities 
    137       pvo  = icb_utl_bilin_h( vo_e, pi, pj, 'V' ) 
    138       psst = icb_utl_bilin_h( tt_e, pi, pj, 'T' )             ! SST 
    139       pcn  = icb_utl_bilin_h( fr_e , pi, pj, 'T' )            ! ice concentration 
    140       pff  = icb_utl_bilin_h( ff_e , pi, pj, 'F' )            ! Coriolis parameter 
    141       ! 
    142       pua  = icb_utl_bilin_h( ua_e , pi, pj, 'U' )            ! 10m wind 
    143       pva  = icb_utl_bilin_h( va_e , pi, pj, 'V' )            ! here (ua,va) are stress => rough conversion from stress to speed 
    144       zcd  = 1.22_wp * 1.5e-3_wp                              ! air density * drag coefficient 
     138      puo  = icb_utl_bilin_h( uo_e, pi, pj, 'U', .false.  )    ! ocean velocities 
     139      pvo  = icb_utl_bilin_h( vo_e, pi, pj, 'V', .false. ) 
     140      psst = icb_utl_bilin_h( tt_e, pi, pj, 'T', .true.   )    ! SST 
     141      pcn  = icb_utl_bilin_h( fr_e, pi, pj, 'T', .true.   )    ! ice concentration 
     142      pff  = icb_utl_bilin_h( ff_e, pi, pj, 'F', .false.  )    ! Coriolis parameter 
     143      ! 
     144      pua  = icb_utl_bilin_h( ua_e, pi, pj, 'U', .true.   )    ! 10m wind 
     145      pva  = icb_utl_bilin_h( va_e, pi, pj, 'V', .true.   )    ! here (ua,va) are stress => rough conversion from stress to speed 
     146      zcd  = 1.22_wp * 1.5e-3_wp                               ! air density * drag coefficient  
    145147      zmod = 1._wp / MAX(  1.e-20, SQRT(  zcd * SQRT( pua*pua + pva*pva)  )  ) 
    146148      pua  = pua * zmod                                       ! note: stress module=0 necessarly implies ua=va=0 
     
    148150 
    149151#if defined key_si3 
    150       pui = icb_utl_bilin_h( ui_e , pi, pj, 'U' )              ! sea-ice velocities 
    151       pvi = icb_utl_bilin_h( vi_e , pi, pj, 'V' ) 
    152       phi = icb_utl_bilin_h( hi_e , pi, pj, 'T' )              ! ice thickness 
     152      pui = icb_utl_bilin_h( ui_e , pi, pj, 'U', .false. )    ! sea-ice velocities 
     153      pvi = icb_utl_bilin_h( vi_e , pi, pj, 'V', .false. ) 
     154      phi = icb_utl_bilin_h( hi_e , pi, pj, 'T', .true.  )    ! ice thickness 
    153155#else 
    154156      pui = 0._wp 
     
    158160 
    159161      ! Estimate SSH gradient in i- and j-direction (centred evaluation) 
    160       pssh_i = ( icb_utl_bilin_h( ssh_e, pi+0.1_wp, pj, 'T' ) -   & 
    161          &       icb_utl_bilin_h( ssh_e, pi-0.1_wp, pj, 'T' )  ) / ( 0.2_wp * pe1 ) 
    162       pssh_j = ( icb_utl_bilin_h( ssh_e, pi, pj+0.1_wp, 'T' ) -   & 
    163          &       icb_utl_bilin_h( ssh_e, pi, pj-0.1_wp, 'T' )  ) / ( 0.2_wp * pe2 ) 
     162      pssh_i = ( icb_utl_bilin_h( ssh_e, pi+0.1_wp, pj, 'T', .true. ) -   & 
     163         &       icb_utl_bilin_h( ssh_e, pi-0.1_wp, pj, 'T', .true. )  ) / ( 0.2_wp * pe1 ) 
     164      pssh_j = ( icb_utl_bilin_h( ssh_e, pi, pj+0.1_wp, 'T', .true. ) -   & 
     165         &       icb_utl_bilin_h( ssh_e, pi, pj-0.1_wp, 'T', .true. )  ) / ( 0.2_wp * pe2 ) 
    164166      ! 
    165167   END SUBROUTINE icb_utl_interp 
    166168 
    167169 
    168    REAL(wp) FUNCTION icb_utl_bilin_h( pfld, pi, pj, cd_type ) 
     170   REAL(wp) FUNCTION icb_utl_bilin_h( pfld, pi, pj, cd_type, plmask ) 
    169171      !!---------------------------------------------------------------------- 
    170172      !!                  ***  FUNCTION icb_utl_bilin  *** 
     
    180182      REAL(wp)                            , INTENT(in) ::   pi, pj    ! targeted coordinates in (i,j) referential 
    181183      CHARACTER(len=1)                    , INTENT(in) ::   cd_type   ! type of pfld array grid-points: = T , U , V or F points 
     184      LOGICAL                             , INTENT(in) ::   plmask    ! special treatment of mask point 
    182185      ! 
    183186      INTEGER  ::   ii, ij   ! local integer 
    184187      REAL(wp) ::   zi, zj   ! local real 
     188      REAL(wp) :: zw1, zw2, zw3, zw4 
     189      REAL(wp), DIMENSION(4) :: zmask 
    185190      !!---------------------------------------------------------------------- 
    186191      ! 
     
    223228      ENDIF 
    224229      ! 
    225       ! 
    226       icb_utl_bilin_h = ( pfld(ii,ij  ) * (1._wp-zi) + pfld(ii+1,ij  ) * zi ) * (1._wp-zj)   & 
    227          &            + ( pfld(ii,ij+1) * (1._wp-zi) + pfld(ii+1,ij+1) * zi ) *        zj 
     230      ! define mask array  
     231      IF (plmask) THEN 
     232         ! land value is not used in the interpolation 
     233         SELECT CASE ( cd_type ) 
     234         CASE ( 'T' ) 
     235            zmask = (/tmask_e(ii,ij), tmask_e(ii+1,ij), tmask_e(ii,ij+1), tmask_e(ii+1,ij+1)/) 
     236         CASE ( 'U' ) 
     237            zmask = (/umask_e(ii,ij), umask_e(ii+1,ij), umask_e(ii,ij+1), umask_e(ii+1,ij+1)/) 
     238         CASE ( 'V' ) 
     239            zmask = (/vmask_e(ii,ij), vmask_e(ii+1,ij), vmask_e(ii,ij+1), vmask_e(ii+1,ij+1)/) 
     240         CASE ( 'F' ) 
     241            ! F case only used for coriolis, ff_f is not mask so zmask = 1 
     242            zmask = 1. 
     243         END SELECT 
     244      ELSE 
     245         ! land value is used during interpolation 
     246         zmask = 1. 
     247      END iF 
     248      ! 
     249      ! compute weight 
     250      zw1 = zmask(1) * (1._wp-zi) * (1._wp-zj) 
     251      zw2 = zmask(2) *        zi  * (1._wp-zj) 
     252      zw3 = zmask(3) * (1._wp-zi) *        zj 
     253      zw4 = zmask(4) *        zi  *        zj 
     254      ! 
     255      ! compute interpolated value 
     256      icb_utl_bilin_h = ( pfld(ii,ij)*zw1 + pfld(ii+1,ij)*zw2 + pfld(ii,ij+1)*zw3 + pfld(ii+1,ij+1)*zw4 ) / MAX(1.e-20, zw1+zw2+zw3+zw4)  
    228257      ! 
    229258   END FUNCTION icb_utl_bilin_h 
  • NEMO/branches/2019/fix_ticket2238_solution1/src/OCE/LBC/mpp_loc_generic.h90

    r10425 r10701  
    1717#      define MPI_OPERATION mpi_maxloc 
    1818#      define LOC_OPERATION MAXLOC 
     19#      define ERRVAL -HUGE 
    1920#   endif 
    2021#   if defined OPERATION_MINLOC 
    2122#      define MPI_OPERATION mpi_minloc 
    2223#      define LOC_OPERATION MINLOC 
     24#      define ERRVAL HUGE 
    2325#   endif 
    2426 
     
    4244      ! 
    4345      idim = SIZE(kindex) 
    44       ALLOCATE ( ilocs(idim) ) 
    4546      ! 
    46       ilocs = LOC_OPERATION( ARRAY_IN(:,:,:) , mask= MASK_IN(:,:,:) == 1._wp ) 
    47       zmin  = ARRAY_IN(ilocs(1),ilocs(2),ilocs(3)) 
    48       ! 
    49       kindex(1) = ilocs(1) + nimpp - 1 
     47      IF ( ALL(MASK_IN(:,:,:) /= 1._wp) ) THEN 
     48         ! special case for land processors 
     49         zmin = ERRVAL(zmin) 
     50         index0 = 0 
     51      ELSE 
     52         ALLOCATE ( ilocs(idim) ) 
     53         ! 
     54         ilocs = LOC_OPERATION( ARRAY_IN(:,:,:) , mask= MASK_IN(:,:,:) == 1._wp ) 
     55         zmin  = ARRAY_IN(ilocs(1),ilocs(2),ilocs(3)) 
     56         ! 
     57         kindex(1) = mig( ilocs(1) ) 
    5058#  if defined DIM_2d || defined DIM_3d    /* avoid warning when kindex has 1 element */ 
    51       kindex(2) = ilocs(2) + njmpp - 1 
     59         kindex(2) = mjg( ilocs(2) ) 
    5260#  endif 
    5361#  if defined DIM_3d                      /* avoid warning when kindex has 2 elements */ 
    54       kindex(3) = ilocs(3) 
     62         kindex(3) = ilocs(3) 
    5563#  endif 
    56       !  
    57       DEALLOCATE (ilocs) 
    58       ! 
    59       index0 = kindex(1)-1   ! 1d index starting at 0 
     64         !  
     65         DEALLOCATE (ilocs) 
     66         ! 
     67         index0 = kindex(1)-1   ! 1d index starting at 0 
    6068#  if defined DIM_2d || defined DIM_3d   /* avoid warning when kindex has 1 element */ 
    61       index0 = index0 + jpiglo * (kindex(2)-1) 
     69         index0 = index0 + jpiglo * (kindex(2)-1) 
    6270#  endif 
    6371#  if defined DIM_3d                     /* avoid warning when kindex has 2 elements */ 
    64       index0 = index0 + jpiglo * jpjglo * (kindex(3)-1) 
     72         index0 = index0 + jpiglo * jpjglo * (kindex(3)-1) 
    6573#  endif 
     74      END IF 
    6675      zain(1,:) = zmin 
    6776      zain(2,:) = REAL(index0, wp) 
Note: See TracChangeset for help on using the changeset viewer.