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 12080 for utils/tools/SIREN/src/interp_nearest.f90 – NEMO

Ignore:
Timestamp:
2019-12-06T10:30:14+01:00 (4 years ago)
Author:
jpaul
Message:

update nemo trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • utils/tools/SIREN/src/interp_nearest.f90

    r9598 r12080  
    22! NEMO system team, System and Interface for oceanic RElocable Nesting 
    33!---------------------------------------------------------------------- 
    4 ! 
    5 ! MODULE: interp 
    64! 
    75! DESCRIPTION: 
     
    2321!> @author 
    2422!> J.Paul 
    25 ! REVISION HISTORY: 
     23!> 
    2624!> @date September, 2014 - Initial version 
    2725!> 
    28 !> @note Software governed by the CeCILL licence     (./LICENSE) 
     26!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    2927!---------------------------------------------------------------------- 
    3028MODULE interp_nearest 
     
    4947   PRIVATE :: interp_nearest__1D_fill  !< fill value using   nearest interpolation 
    5048 
    51 CONTAINS    
     49CONTAINS 
     50   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
     51   SUBROUTINE interp_nearest_fill(dd_value, id_detect, id_rho) 
    5252   !------------------------------------------------------------------- 
    5353   !> @brief 
     
    6161   !> @param[in]    id_rho    array of refinment factor 
    6262   !------------------------------------------------------------------- 
    63    SUBROUTINE interp_nearest_fill(dd_value, id_detect, id_rho ) 
    64       IMPLICIT NONE 
     63 
     64      IMPLICIT NONE 
     65 
    6566      ! Argument 
    6667      REAL(dp)        , DIMENSION(:,:,:,:), INTENT(INOUT) :: dd_value  
     
    118119 
    119120   END SUBROUTINE interp_nearest_fill 
     121   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
     122   SUBROUTINE interp_nearest__2D(dd_value, id_detect, id_rhoi, id_rhoj) 
    120123   !------------------------------------------------------------------- 
    121124   !> @brief 
     
    131134   !> @param[in] id_rhok      refinment factor in k-direction 
    132135   !------------------------------------------------------------------- 
    133    SUBROUTINE interp_nearest__2D( dd_value, id_detect, & 
    134       &                           id_rhoi, id_rhoj ) 
    135  
    136       IMPLICIT NONE 
     136 
     137      IMPLICIT NONE 
     138 
    137139      ! Argument 
    138140      REAL(dp)        , DIMENSION(:,:), INTENT(INOUT) :: dd_value  
     
    173175 
    174176   END SUBROUTINE interp_nearest__2D 
     177   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
     178   SUBROUTINE interp_nearest__1D(dd_value, id_detect, id_rhoi) 
    175179   !------------------------------------------------------------------- 
    176180   !> @brief 
     
    184188   !> @param[in]    id_rhoi   refinment factor 
    185189   !------------------------------------------------------------------- 
    186    SUBROUTINE interp_nearest__1D( dd_value,  id_detect, & 
    187       &                           id_rhoi ) 
    188  
    189       IMPLICIT NONE 
     190 
     191      IMPLICIT NONE 
     192 
    190193      ! Argument 
    191194      REAL(dp)        , DIMENSION(:), INTENT(INOUT) :: dd_value  
     
    198201      ! loop indices 
    199202      INTEGER(i4) :: ji 
    200  
    201203      !---------------------------------------------------------------- 
    202204 
     
    218220 
    219221   END SUBROUTINE interp_nearest__1D 
     222   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
     223   SUBROUTINE interp_nearest__2D_fill(dd_value, id_detect) 
    220224   !------------------------------------------------------------------- 
    221225   !> @brief 
     
    228232   !> @param[inout] id_detect 2D array of point to be interpolated 
    229233   !------------------------------------------------------------------- 
    230    SUBROUTINE interp_nearest__2D_fill( dd_value, id_detect ) 
    231       IMPLICIT NONE 
     234 
     235      IMPLICIT NONE 
     236 
    232237      ! Argument 
    233238      REAL(dp)   , DIMENSION(:,:)  , INTENT(INOUT) :: dd_value  
     
    302307 
    303308   END SUBROUTINE interp_nearest__2D_fill 
     309   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
     310   SUBROUTINE interp_nearest__1D_fill(dd_value, id_detect) 
    304311   !------------------------------------------------------------------- 
    305312   !> @brief 
     
    312319   !> @param[inout] id_detect 1D array of point to be interpolated 
    313320   !------------------------------------------------------------------- 
    314    SUBROUTINE interp_nearest__1D_fill( dd_value, id_detect ) 
    315       IMPLICIT NONE 
     321 
     322      IMPLICIT NONE 
     323 
    316324      ! Argument 
    317325      REAL(dp)   , DIMENSION(:), INTENT(INOUT) :: dd_value  
     
    358366 
    359367   END SUBROUTINE interp_nearest__1D_fill 
     368   !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
    360369END MODULE interp_nearest 
Note: See TracChangeset for help on using the changeset viewer.