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

Ignore:
Timestamp:
2018-09-05T15:33:44+02:00 (6 years ago)
Author:
rblod
Message:

update AGRIF library

File:
1 edited

Legend:

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

    r5656 r10087  
    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 
    719contains 
    820! 
     
    1426subroutine Agrif_Declare_Variable ( posvar, firstpoint, raf, lb, ub, varid, torestore ) 
    1527!--------------------------------------------------------------------------------------------------- 
    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 !--------------------------------------------------------------------------------------------------- 
     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! 
    2638    type(Agrif_Variables_List), pointer :: new_varlist 
    2739    type(Agrif_Variable),       pointer :: var 
    28     integer                             :: nbdim, i 
     40    integer                             :: nbdim 
    2941    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 
    3048 
    3149    restore = .FALSE. 
     
    4361    allocate(var % posvar(nbdim)) 
    4462    allocate(var % interptab(nbdim)) 
    45     allocate(var % coords(nbdim)) 
    4663! 
    47     var % nbdim          = nbdim 
    48     var % interptab      = raf(1:nbdim) 
    49     var % posvar         = posvar(1:nbdim) 
    50     var % point(1:nbdim) = firstpoint(1:nbdim) 
     64    var % interptab = raf 
     65    var % nbdim = nbdim 
     66    var % posvar = posvar 
     67    var % point(1:nbdim) = firstpoint 
    5168    var % restore = restore 
    52 ! 
     69 
     70    var % lb(1:nbdim) = lb(1:nbdim) 
     71    var % ub(1:nbdim) = ub(1:nbdim) 
     72 
     73#if defined AGRIF_MPI 
    5374    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 
     75        call Agrif_Invloc(lb(i), Agrif_Procrank, i, iminmaxg(i,1)) 
     76        call Agrif_Invloc(ub(i), Agrif_Procrank, i, iminmaxg(i,2)) 
    6177    enddo 
    6278! 
    63     var % lb(1:nbdim) = lb(1:nbdim) 
    64     var % ub(1:nbdim) = ub(1:nbdim) 
     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 
    6588 
    6689    if ( restore ) then 
     
    121144    integer :: nb, varidinv 
    122145! 
    123     if ( .not.associated(grid) ) then 
     146    if ( .not.associated(grid)) then 
    124147        outvar => NULL() 
    125148        return 
     
    127150! 
    128151    parcours => grid % variables 
    129  
     152     
    130153    if (.not. associated(parcours)) then   ! can occur on the grand mother grid 
    131154           outvar => NULL()                ! during the first call by agrif_mygrid 
    132155           return 
    133156    endif 
    134  
     157                                            
     158     
    135159    varidinv = 1 + grid % nbvariables - varid 
    136160 
     
    140164 
    141165    outvar => parcours % var 
     166 
    142167!--------------------------------------------------------------------------------------------------- 
    143168end function Agrif_Search_variable 
Note: See TracChangeset for help on using the changeset viewer.