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 9987 for branches/UKMO/dev_r5518_obs_oper_update_icethick/NEMOGCM/TOOLS/SIREN/src/interp_nearest.f90 – NEMO

Ignore:
Timestamp:
2018-07-23T11:33:03+02:00 (6 years ago)
Author:
emmafiedler
Message:

Merge with GO6 FOAMv14 package branch r9288

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_obs_oper_update_icethick/NEMOGCM/TOOLS/SIREN/src/interp_nearest.f90

    r5037 r9987  
    2424!> J.Paul 
    2525! REVISION HISTORY: 
    26 !> @date September, 2014 -Initial version 
     26!> @date September, 2014 - Initial version 
    2727!> 
    2828!> @note Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    5555   !>  
    5656   !> @author J.Paul 
    57    !> - September, 2014- Initial Version 
     57   !> @date September, 2014 - Initial Version 
    5858   !> 
    5959   !> @param[inout] dd_value  2D array of variable value  
     
    6969 
    7070      ! local variable 
    71       INTEGER(i4), DIMENSION(4)                :: il_shape 
     71      INTEGER(i4), DIMENSION(4)                  :: il_shape 
     72 
     73      INTEGER(I4), DIMENSION(:,:,:), ALLOCATABLE :: il_detect 
    7274 
    7375      ! loop indices 
     
    8082      il_shape(:)=SHAPE(dd_value) 
    8183 
     84      ALLOCATE(il_detect(il_shape(1),il_shape(2),il_shape(3))) 
    8285      DO jl=1,il_shape(4) 
     86         il_detect(:,:,:)=id_detect(:,:,:) 
    8387         ! loop on vertical level 
    8488         DO jk=1,il_shape(3) 
     
    8690            ! I-J plan 
    8791            CALL interp_nearest__2D(dd_value(:,:,jk,jl),& 
    88             &                       id_detect(:,:,jk),  & 
     92            &                       il_detect(:,:,jk),  & 
    8993            &                       id_rho(jp_I), id_rho(jp_J) )             
    90             IF( ANY(id_detect(:,:,jk)==1) )THEN 
     94            IF( ANY(il_detect(:,:,jk)==1) )THEN 
    9195               ! I direction 
    9296               DO jj=1,il_shape(2) 
    9397                  CALL interp_nearest__1D( dd_value(:,jj,jk,jl),& 
    94                   &                        id_detect(:,jj,jk),  & 
     98                  &                        il_detect(:,jj,jk),  & 
    9599                  &                        id_rho(jp_I) ) 
    96100               ENDDO 
    97                IF( ALL(id_detect(:,:,jk)==0) )THEN 
     101               IF( ALL(il_detect(:,:,jk)==0) )THEN 
    98102                  CYCLE 
    99103               ELSE 
     
    101105                  DO ji=1,il_shape(1) 
    102106                     CALL interp_nearest__1D( dd_value(ji,:,jk,jl),& 
    103                      &                        id_detect(ji,:,jk),  & 
     107                     &                        il_detect(ji,:,jk),  & 
    104108                     &                        id_rho(jp_J) ) 
    105109                  ENDDO 
     
    110114      ENDDO 
    111115 
     116      id_detect(:,:,:)=il_detect(:,:,:) 
     117      DEALLOCATE(il_detect) 
     118 
    112119   END SUBROUTINE interp_nearest_fill 
    113120   !------------------------------------------------------------------- 
     
    116123   !>  
    117124   !> @author J.Paul 
    118    !> - September, 2014- Initial Version 
     125   !> @date September, 2014 - Initial Version 
    119126   !> 
    120127   !> @param[inout] dd_value  2D array of variable value  
     
    171178   !>  
    172179   !> @author J.Paul 
    173    !> - September, 2014- Initial Version 
     180   !> @date September, 2014 - Initial Version 
    174181   !> 
    175182   !> @param[inout] dd_value  1D array of variable value  
     
    216223   !>  
    217224   !> @author J.Paul 
    218    !> - September, 2014- Initial Version 
     225   !> @date September, 2014 - Initial Version 
    219226   !> 
    220227   !> @param[inout] dd_value  2D array of mixed grid value 
     
    300307   !>  
    301308   !> @author J.Paul 
    302    !> - September, 2014- Initial Version 
     309   !> @date September, 2014 - Initial Version 
    303310   !> 
    304311   !> @param[inout] dd_value  1D array of mixed grid value 
Note: See TracChangeset for help on using the changeset viewer.