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 10725 for vendors/AGRIF/CMEMS_2020/AGRIF_FILES/modvariables.F90 – NEMO

Ignore:
Timestamp:
2019-02-27T14:55:54+01:00 (5 years ago)
Author:
rblod
Message:

Update agrif library and conv see ticket #2129

File:
1 edited

Legend:

Unmodified
Added
Removed
  • vendors/AGRIF/CMEMS_2020/AGRIF_FILES/modvariables.F90

    r10087 r10725  
    55    implicit none 
    66! 
    7 #if defined AGRIF_MPI 
    8     interface 
    9         subroutine Agrif_InvLoc ( indloc, proc_id, dir, indglob ) 
    10             integer, intent(in)     :: indloc   !< local index 
    11             integer, intent(in)     :: proc_id  !< rank of the proc calling this function 
    12             integer, intent(in)     :: dir      !< direction of the index 
    13             integer, intent(out)    :: indglob  !< global index 
    14         end subroutine Agrif_InvLoc 
    15     end interface 
    16     private :: Agrif_InvLoc 
    17 #endif 
    18  
    197contains 
    208! 
     
    2614subroutine Agrif_Declare_Variable ( posvar, firstpoint, raf, lb, ub, varid, torestore ) 
    2715!--------------------------------------------------------------------------------------------------- 
    28     integer, dimension(:),      intent(in)      :: posvar     !< position of the variable on the cell 
    29                                                               !< (1 for the border of the edge, 2 for the center) 
    30     integer, dimension(:),      intent(in)      :: firstpoint !< index of the first point in the real domain 
    31     character(*), dimension(:), intent(in)      :: raf        !< Array indicating the type of dimension (space or not) 
    32                                                               !<   for each of them 
    33     integer, dimension(:),      intent(in)      :: lb         !< Lower bounds of the array 
    34     integer, dimension(:),      intent(in)      :: ub         !< Upper bounds of the array 
    35     integer,                    intent(out)     :: varid      !< Id number of the newly created variable 
    36     logical, optional,          intent(in)      :: torestore  !< Indicates if the array restore is used 
    37 ! 
     16    integer,      dimension(:), intent(in)  :: posvar     !< position of the variable on the cell 
     17                                                          !! (1 for the border of the edge, 2 for the center) 
     18    integer,      dimension(:), intent(in)  :: firstpoint !< index of the first point in the real domain 
     19    character(1), dimension(:), intent(in)  :: raf        !< Array indicating the type of dimension (space or not) 
     20                                                          !!   for each of them 
     21    integer,      dimension(:), intent(in)  :: lb         !< Lower bounds of the array 
     22    integer,      dimension(:), intent(in)  :: ub         !< Upper bounds of the array 
     23    integer,                    intent(out) :: varid      !< Id number of the newly created variable 
     24    logical,      optional,     intent(in)  :: torestore  !< Indicates if the array restore is used 
     25!--------------------------------------------------------------------------------------------------- 
    3826    type(Agrif_Variables_List), pointer :: new_varlist 
    3927    type(Agrif_Variable),       pointer :: var 
    40     integer                             :: nbdim 
     28    integer                             :: nbdim, i 
    4129    logical                             :: restore 
    42 #if defined AGRIF_MPI 
    43     include 'mpif.h' 
    44     integer :: i 
    45     integer,dimension(6,2) :: iminmaxg, lubglob 
    46     integer :: code 
    47 #endif 
    4830 
    4931    restore = .FALSE. 
     
    6143    allocate(var % posvar(nbdim)) 
    6244    allocate(var % interptab(nbdim)) 
     45    allocate(var % coords(nbdim)) 
    6346! 
    64     var % interptab = raf 
    65     var % nbdim = nbdim 
    66     var % posvar = posvar 
    67     var % point(1:nbdim) = firstpoint 
     47    var % nbdim          = nbdim 
     48    var % interptab      = raf(1:nbdim) 
     49    var % posvar         = posvar(1:nbdim) 
     50    var % point(1:nbdim) = firstpoint(1:nbdim) 
    6851    var % restore = restore 
    69  
     52! 
     53    do i = 1,nbdim 
     54        select case( raf(i) ) 
     55            case('x')    ; var % coords(i) = 1 
     56            case('y')    ; var % coords(i) = 2 
     57            case('z')    ; var % coords(i) = 3 
     58            case('N')    ; var % coords(i) = 0 
     59            case default ; var % coords(i) = 0 
     60        end select 
     61    enddo 
     62! 
    7063    var % lb(1:nbdim) = lb(1:nbdim) 
    7164    var % ub(1:nbdim) = ub(1:nbdim) 
    72  
    73 #if defined AGRIF_MPI 
    74     do i = 1,nbdim 
    75         call Agrif_Invloc(lb(i), Agrif_Procrank, i, iminmaxg(i,1)) 
    76         call Agrif_Invloc(ub(i), Agrif_Procrank, i, iminmaxg(i,2)) 
    77     enddo 
    78 ! 
    79     iminmaxg(1:nbdim,2) = - iminmaxg(1:nbdim,2) 
    80     call MPI_ALLREDUCE(iminmaxg(1:nbdim,:), lubglob(1:nbdim,:), 2*nbdim, MPI_INTEGER,MPI_MIN,Agrif_mpi_comm, code) 
    81     lubglob(1:nbdim,2)  = - lubglob(1:nbdim,2) 
    82     var % lbglob(1:nbdim) = lubglob(1:nbdim,1) 
    83     var % ubglob(1:nbdim) = lubglob(1:nbdim,2) 
    84 #else 
    85     var % lbglob(1:nbdim) = var % lb(1:nbdim) 
    86     var % ubglob(1:nbdim) = var % ub(1:nbdim) 
    87 #endif 
    8865 
    8966    if ( restore ) then 
     
    12299    Agrif_Curgrid % Nbvariables = Agrif_Curgrid % Nbvariables + 1 
    123100 
    124     varid = -Agrif_Curgrid % Nbvariables 
     101    varid = Agrif_Curgrid % Nbvariables 
    125102 
    126103    var % parent_var => Agrif_Search_Variable(Agrif_Curgrid % parent, Agrif_Curgrid % nbvariables) 
     
    144121    integer :: nb, varidinv 
    145122! 
    146     if ( .not.associated(grid)) then 
     123    if ( .not.associated(grid) ) then 
    147124        outvar => NULL() 
    148125        return 
     
    150127! 
    151128    parcours => grid % variables 
    152      
     129 
    153130    if (.not. associated(parcours)) then   ! can occur on the grand mother grid 
    154131           outvar => NULL()                ! during the first call by agrif_mygrid 
    155132           return 
    156133    endif 
    157                                             
    158      
     134 
    159135    varidinv = 1 + grid % nbvariables - varid 
    160136 
     
    164140 
    165141    outvar => parcours % var 
    166  
    167142!--------------------------------------------------------------------------------------------------- 
    168143end function Agrif_Search_variable 
Note: See TracChangeset for help on using the changeset viewer.