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 8138 – NEMO

Changeset 8138


Ignore:
Timestamp:
2017-06-05T12:01:03+02:00 (7 years ago)
Author:
timgraham
Message:

Modifications to AGRIF_FILES as received from Laurent (need to check that these are definitely needed)

Location:
branches/2017/dev_r8126_UKMO_AGRIF_vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r8126_UKMO_AGRIF_vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modarrays.F90

    r5656 r8138  
    5555                               proc_id,         & 
    5656                               coords,          & 
    57                                lb_tab_true, ub_tab_true, memberin ) 
     57                               lb_tab_true, ub_tab_true, memberin,  & 
     58                               indminglob3,indmaxglob3) 
    5859!--------------------------------------------------------------------------------------------------- 
    5960    integer,                   intent(in)  :: nbdim         !< Number of dimensions 
     
    6162    integer, dimension(nbdim), intent(in)  :: ub_var        !< Local upper boundary on the current processor 
    6263    integer, dimension(nbdim), intent(in)  :: lb_tab        !< Global lower boundary of the variable 
     64    integer, dimension(nbdim),OPTIONAL     :: indminglob3,indmaxglob3 !< True bounds for MPI USE 
    6365    integer, dimension(nbdim), intent(in)  :: ub_tab        !< Global upper boundary of the variable 
    6466    integer,                   intent(in)  :: proc_id       !< Current processor 
     
    7880        call Agrif_InvLoc( lb_var(i), proc_id, coord_i, lb_glob_index ) 
    7981        call Agrif_InvLoc( ub_var(i), proc_id, coord_i, ub_glob_index ) 
     82        if (present(indminglob3)) then 
     83          indminglob3(i)=lb_glob_index 
     84          indmaxglob3(i)=ub_glob_index 
     85        endif 
    8086#else 
    8187        lb_glob_index = lb_var(i) 
     
    123129! 
    124130    iminmaxg(1:nbdim,2) = - iminmaxg(1:nbdim,2) 
    125     call MPI_ALLREDUCE(iminmaxg, lubglob, 2*nbdim, MPI_INTEGER, MPI_MIN, Agrif_mpi_comm, code) 
     131    call MPI_ALLREDUCE(iminmaxg, lubglob, 2*nbdim, MPI_INTEGER, MPI_MIN, & 
     132                       Agrif_mpi_comm, code) 
    126133    lubglob(1:nbdim,2)  = - lubglob(1:nbdim,2) 
    127134#endif 
     
    803810    do i = 1,nbdim 
    804811! 
     812     if (coords(i) == 0) then 
     813       nbloc(i) = 1 
     814       locbounds(i,1,1) = lb_glob(i) 
     815       locbounds(i,2,1) = ub_glob(i) 
     816       locbounds(i,1,2) = lb_glob(i) 
     817       locbounds(i,2,2) = ub_glob(i) 
     818     else 
    805819        call Agrif_InvLoc(lb_var(i), rank, coords(i), i1) 
    806820! 
     
    816830            endif 
    817831        enddo 
     832     endif 
    818833    enddo 
    819834 
  • branches/2017/dev_r8126_UKMO_AGRIF_vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modbcfunction.F90

    r5656 r8138  
    5858    integer, intent(in)     :: value        !< input value 
    5959! 
    60     Agrif_Curgrid % parent % tabvars_i(tabvarsindic) % iarray0 = value 
     60 
     61integer :: i 
     62logical :: i_found 
     63 
     64i_found = .FALSE. 
     65 
     66do i=1,Agrif_NbVariables(4) 
     67  if (LOC(tabvarsindic) == LOC(agrif_curgrid%tabvars_i(i)%iarray0)) then 
     68     agrif_curgrid%tabvars_i(i)%parent_var%iarray0 = value 
     69     i_found = .TRUE. 
     70     EXIT 
     71  endif 
     72enddo 
     73 
     74if (.NOT.i_found) STOP 'Agrif_Set_Integer : Variable not found' 
     75 
    6176!--------------------------------------------------------------------------------------------------- 
    6277end subroutine Agrif_Set_parent_int 
     
    7085subroutine Agrif_Set_parent_real4 ( tabvarsindic, value ) 
    7186!--------------------------------------------------------------------------------------------------- 
    72     integer, intent(in)     :: tabvarsindic !< indice of the variable in tabvars 
    73     real(kind=4),intent(in) :: value        !< input value 
    74 ! 
    75     Agrif_Curgrid % parent % tabvars_r(tabvarsindic) % array0 = value 
    76     Agrif_Curgrid % parent % tabvars_r(tabvarsindic) % sarray0 = value 
     87    real(kind=4), intent(in)     :: tabvarsindic !< input variable 
     88    real(kind=4),intent(in) :: value        !< input value for the parent grid 
     89 
     90integer :: i 
     91logical :: i_found 
     92 
     93i_found = .FALSE. 
     94 
     95do i=1,Agrif_NbVariables(2) 
     96  if (LOC(tabvarsindic) == LOC(agrif_curgrid%tabvars_r(i)%array0)) then 
     97     agrif_curgrid%tabvars_r(i)%parent_var%array0 = value 
     98     agrif_curgrid%tabvars_r(i)%parent_var%sarray0 = value 
     99     i_found = .TRUE. 
     100     EXIT 
     101  endif 
     102enddo 
     103 
     104IF (.NOT.i_found) THEN 
     105do i=1,Agrif_NbVariables(2) 
     106  if (LOC(tabvarsindic) == LOC(agrif_curgrid%tabvars_r(i)%sarray0)) then 
     107     agrif_curgrid%tabvars_r(i)%parent_var%array0 = value 
     108     agrif_curgrid%tabvars_r(i)%parent_var%sarray0 = value 
     109     i_found = .TRUE. 
     110     EXIT 
     111  endif 
     112enddo 
     113ENDIF 
     114 
     115if (.NOT.i_found) STOP 'Agrif_Set_parent_real4 : Variable not found' 
    77116!--------------------------------------------------------------------------------------------------- 
    78117end subroutine Agrif_Set_parent_real4 
     
    86125subroutine Agrif_Set_parent_real8 ( tabvarsindic, value ) 
    87126!--------------------------------------------------------------------------------------------------- 
    88     integer, intent(in)     :: tabvarsindic !< indice of the variable in tabvars 
    89     real(kind=8),intent(in) :: value        !< input value 
    90 ! 
    91     Agrif_Curgrid % parent % tabvars_r(tabvarsindic) % darray0 = value 
     127    real(kind=8), intent(in)     :: tabvarsindic !< input variable 
     128    real(kind=8),intent(in) :: value        !< input value for the parent grid 
     129 
     130integer :: i 
     131logical :: i_found 
     132 
     133i_found = .FALSE. 
     134 
     135do i=1,Agrif_NbVariables(2) 
     136  if (LOC(tabvarsindic) == LOC(agrif_curgrid%tabvars_r(i)%array0)) then 
     137     agrif_curgrid%tabvars_r(i)%parent_var%darray0 = value 
     138     agrif_curgrid%tabvars_r(i)%parent_var%array0 = value 
     139     i_found = .TRUE. 
     140     EXIT 
     141  endif 
     142enddo 
     143 
     144IF (.NOT.i_found) THEN 
     145do i=1,Agrif_NbVariables(2) 
     146  if (LOC(tabvarsindic) == LOC(agrif_curgrid%tabvars_r(i)%darray0)) then 
     147     agrif_curgrid%tabvars_r(i)%parent_var%darray0 = value 
     148     agrif_curgrid%tabvars_r(i)%parent_var%array0 = value 
     149     i_found = .TRUE. 
     150     EXIT 
     151  endif 
     152enddo 
     153ENDIF 
     154 
     155if (.NOT.i_found) STOP 'Agrif_Set_parent_real8 : Variable not found' 
     156 
    92157!--------------------------------------------------------------------------------------------------- 
    93158end subroutine Agrif_Set_parent_real8 
  • branches/2017/dev_r8126_UKMO_AGRIF_vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modcurgridfunctions.F90

    r5656 r8138  
    2929    implicit none 
    3030! 
     31 
     32    interface Agrif_Parent 
     33        module procedure Agrif_Parent_Real_4,   & 
     34                         Agrif_Parent_Real_8,   & 
     35                         Agrif_Parent_Integer, & 
     36                         Agrif_Parent_Character, & 
     37                         Agrif_Parent_Logical 
     38    end interface 
     39     
    3140contains 
    3241! 
     
    763772!=================================================================================================== 
    764773! 
     774 
     775function Agrif_Parent_Real_4(real_variable) result(real_variable_parent) 
     776real(KIND=4) :: real_variable 
     777real(KIND=4) :: real_variable_parent 
     778 
     779integer :: i 
     780logical :: i_found 
     781 
     782i_found = .FALSE. 
     783 
     784do i=1,Agrif_NbVariables(2) 
     785  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%array0)) then 
     786     real_variable_parent = agrif_curgrid%tabvars_r(i)%parent_var%array0 
     787     i_found = .TRUE. 
     788     EXIT 
     789  endif 
     790enddo 
     791 
     792IF (.NOT.i_found) THEN 
     793do i=1,Agrif_NbVariables(2) 
     794  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%sarray0)) then 
     795     real_variable_parent = agrif_curgrid%tabvars_r(i)%parent_var%sarray0 
     796     i_found = .TRUE. 
     797     EXIT 
     798  endif 
     799enddo 
     800ENDIF 
     801 
     802if (.NOT.i_found) STOP 'Agrif_Parent_Real_4 : Variable not found' 
     803 
     804end function Agrif_Parent_Real_4 
     805 
     806function Agrif_Parent_Real_8(real_variable) result(real_variable_parent) 
     807real(KIND=8) :: real_variable 
     808real(KIND=8) :: real_variable_parent 
     809 
     810integer :: i 
     811logical :: i_found 
     812 
     813i_found = .FALSE. 
     814 
     815do i=1,Agrif_NbVariables(2) 
     816  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%array0)) then 
     817     real_variable_parent = agrif_curgrid%tabvars_r(i)%parent_var%array0 
     818     i_found = .TRUE. 
     819     EXIT 
     820  endif 
     821enddo 
     822 
     823IF (.NOT.i_found) THEN 
     824do i=1,Agrif_NbVariables(2) 
     825  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%darray0)) then 
     826     real_variable_parent = agrif_curgrid%tabvars_r(i)%parent_var%darray0 
     827     i_found = .TRUE. 
     828     EXIT 
     829  endif 
     830enddo 
     831ENDIF 
     832 
     833if (.NOT.i_found) STOP 'Agrif_Parent_Real_8 : Variable not found' 
     834 
     835end function Agrif_Parent_Real_8 
     836 
     837function Agrif_Parent_Integer(integer_variable) result(integer_variable_parent) 
     838integer :: integer_variable 
     839integer :: integer_variable_parent 
     840 
     841integer :: i 
     842logical :: i_found 
     843 
     844i_found = .FALSE. 
     845 
     846do i=1,Agrif_NbVariables(4) 
     847  if (LOC(integer_variable) == LOC(agrif_curgrid%tabvars_i(i)%iarray0)) then 
     848     integer_variable_parent = agrif_curgrid%tabvars_i(i)%parent_var%iarray0 
     849     i_found = .TRUE. 
     850     EXIT 
     851  endif 
     852enddo 
     853 
     854if (.NOT.i_found) STOP 'Agrif_Parent : Variable not found' 
     855 
     856end function Agrif_Parent_Integer 
     857 
     858function Agrif_Parent_Character(character_variable) result(character_variable_parent) 
     859character(*) :: character_variable 
     860character(len(character_variable)) :: character_variable_parent 
     861 
     862integer :: i 
     863logical :: i_found 
     864 
     865i_found = .FALSE. 
     866 
     867do i=1,Agrif_NbVariables(1) 
     868  if (LOC(character_variable) == LOC(agrif_curgrid%tabvars_c(i)%carray0)) then 
     869     character_variable_parent = agrif_curgrid%tabvars_c(i)%parent_var%carray0 
     870     i_found = .TRUE. 
     871     EXIT 
     872  endif 
     873enddo 
     874 
     875if (.NOT.i_found) STOP 'Agrif_Parent : Variable not found' 
     876 
     877end function Agrif_Parent_Character 
     878 
     879function Agrif_Parent_Logical(logical_variable) result(logical_variable_parent) 
     880logical :: logical_variable 
     881logical :: logical_variable_parent 
     882 
     883integer :: i 
     884logical :: i_found 
     885 
     886i_found = .FALSE. 
     887 
     888do i=1,Agrif_NbVariables(3) 
     889  if (LOC(logical_variable) == LOC(agrif_curgrid%tabvars_l(i)%larray0)) then 
     890     logical_variable_parent = agrif_curgrid%tabvars_l(i)%parent_var%larray0 
     891     i_found = .TRUE. 
     892     EXIT 
     893  endif 
     894enddo 
     895 
     896if (.NOT.i_found) STOP 'Agrif_Parent : Variable not found' 
     897 
     898end function Agrif_Parent_Logical 
     899 
     900function Agrif_Irhox() result(i_val) 
     901integer :: i_val 
     902i_val = agrif_curgrid%spaceref(1) 
     903end function Agrif_Irhox 
     904 
     905function Agrif_Irhoy() result(i_val) 
     906integer :: i_val 
     907i_val = agrif_curgrid%spaceref(2) 
     908end function Agrif_Irhoy 
     909 
     910function Agrif_Irhoz() result(i_val) 
     911integer :: i_val 
     912i_val = agrif_curgrid%spaceref(3) 
     913end function Agrif_Irhoz 
     914 
     915function Agrif_NearCommonBorderX() result(l_val) 
     916logical :: l_val 
     917l_val = agrif_curgrid%nearRootBorder(1) 
     918end function Agrif_NearCommonBorderX 
     919 
     920function Agrif_NearCommonBorderY() result(l_val) 
     921logical :: l_val 
     922l_val = agrif_curgrid%nearRootBorder(2) 
     923end function Agrif_NearCommonBorderY 
     924 
     925function Agrif_NearCommonBorderZ() result(l_val) 
     926logical :: l_val 
     927l_val = agrif_curgrid%nearRootBorder(3) 
     928end function Agrif_NearCommonBorderZ 
     929 
     930function Agrif_DistantCommonBorderX() result(l_val) 
     931logical :: l_val 
     932l_val = agrif_curgrid%DistantRootBorder(1) 
     933end function Agrif_DistantCommonBorderX 
     934 
     935function Agrif_DistantCommonBorderY() result(l_val) 
     936logical :: l_val 
     937l_val = agrif_curgrid%DistantRootBorder(2) 
     938end function Agrif_DistantCommonBorderY 
     939 
     940function Agrif_DistantCommonBorderZ() result(l_val) 
     941logical :: l_val 
     942l_val = agrif_curgrid%DistantRootBorder(3) 
     943end function Agrif_DistantCommonBorderZ 
     944 
     945function Agrif_Ix() result(i_val) 
     946integer :: i_val 
     947i_val = agrif_curgrid%ix(1) 
     948end function Agrif_Ix 
     949 
     950function Agrif_Iy() result(i_val) 
     951integer :: i_val 
     952i_val = agrif_curgrid%ix(2) 
     953end function Agrif_Iy 
     954 
     955function Agrif_Iz() result(i_val) 
     956integer :: i_val 
     957i_val = agrif_curgrid%ix(3) 
     958end function Agrif_Iz 
     959 
     960function Agrif_Get_grid_id() result(i_val) 
     961integer :: i_val 
     962i_val = agrif_curgrid % grid_id 
     963end function Agrif_Get_grid_id 
     964 
     965function Agrif_Get_parent_id() result(i_val) 
     966integer :: i_val 
     967i_val = agrif_curgrid % parent % grid_id 
     968end function Agrif_Get_parent_id 
     969 
     970function Agrif_rhox() result(r_val) 
     971real :: r_val 
     972r_val = real(agrif_curgrid%spaceref(1)) 
     973end function Agrif_rhox 
     974 
     975function Agrif_rhoy() result(r_val) 
     976real :: r_val 
     977r_val = real(agrif_curgrid%spaceref(2)) 
     978end function Agrif_rhoy 
     979 
     980function Agrif_rhoz() result(r_val) 
     981real :: r_val 
     982r_val = real(agrif_curgrid%spaceref(3)) 
     983end function Agrif_rhoz 
     984 
     985function Agrif_Nb_Step() result(i_val) 
     986integer :: i_val 
     987i_val = agrif_curgrid%ngridstep 
     988end function Agrif_Nb_Step 
     989 
     990function Agrif_Nb_Fine_Grids() result(i_val) 
     991integer :: i_val 
     992i_val = Agrif_nbfixedgrids 
     993end function Agrif_Nb_Fine_Grids 
     994 
    765995end module Agrif_CurgridFunctions 
  • branches/2017/dev_r8126_UKMO_AGRIF_vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modinterp.F90

    r7752 r8138  
    132132#if defined AGRIF_MPI 
    133133    INTEGER, DIMENSION(nbdim)     :: indminglob2,indmaxglob2 
     134    INTEGER, DIMENSION(nbdim)     :: indminglob3,indmaxglob3 
    134135#endif 
    135136    LOGICAL, DIMENSION(nbdim)     :: noraftab 
     
    148149    INTEGER, DIMENSION(nbdim,4,0:Agrif_Nbprocs-1)   :: tab4 
    149150    INTEGER, DIMENSION(nbdim,0:Agrif_Nbprocs-1,8)   :: tab4t 
     151    INTEGER,DIMENSION(nbdim,2) :: tab5 
     152    INTEGER,DIMENSION(nbdim,2,0:Agrif_Nbprocs-1) :: tab6 
     153    INTEGER,DIMENSION(nbdim,0:Agrif_Nbprocs-1,2) :: tab5t 
    150154    LOGICAL, DIMENSION(0:Agrif_Nbprocs-1)           :: memberinall 
    151155    LOGICAL, DIMENSION(0:Agrif_Nbprocs-1)           :: sendtoproc1, recvfromproc1 
     
    205209        call Agrif_Childbounds(nbdim,lowerbound,upperbound,                 & 
    206210                               indminglob,indmaxglob, local_proc, coords,   & 
    207                                indminglob2,indmaxglob2,member) 
     211                               indminglob2,indmaxglob2,member,              & 
     212                               indminglob3,indmaxglob3) 
    208213! 
    209214        if (member) then 
     
    224229        member = .TRUE. 
    225230#endif 
     231!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
     232! Correct for non refined directions 
     233!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
     234        do i=1,nbdim 
     235          if (coords(i) == 0) then 
     236             indmin(i) = indminglob(i) 
     237             indmax(i) = indmaxglob(i) 
     238             pttruetab(i) = indminglob(i) 
     239             cetruetab(i) = indmaxglob(i) 
     240          endif 
     241        enddo 
    226242 
    227243    else 
     
    298314        tab3(:,3) = indmin(:) 
    299315        tab3(:,4) = indmax(:) 
     316        tab5(:,1) = indminglob3(:) 
     317        tab5(:,2) = indmaxglob3(:) 
    300318! 
    301319        call MPI_ALLGATHER(tab3,4*nbdim,MPI_INTEGER,tab4,4*nbdim,MPI_INTEGER,Agrif_mpi_comm,code) 
    302  
     320        call MPI_ALLGATHER(tab5,2*nbdim,MPI_INTEGER,tab6,2*nbdim,MPI_INTEGER,Agrif_mpi_comm,code) 
    303321        if (.not.associated(tempPextend))   allocate(tempPextend) 
    304322 
     
    311329        enddo 
    312330 
     331        do k=0,Agrif_Nbprocs-1 
     332          do j=1,2 
     333            do i=1,nbdim 
     334               tab5t(i,k,j) = tab6(i,j,k) 
     335            enddo 
     336          enddo 
     337        enddo 
     338       
    313339        memberin1(1) = memberin 
    314340        call MPI_ALLGATHER(memberin1,1,MPI_LOGICAL,memberinall,1,MPI_LOGICAL,Agrif_mpi_comm,code) 
     
    319345                                     sendtoproc1,recvfromproc1,         & 
    320346                                     tab4t(:,:,5),tab4t(:,:,6),         & 
    321                                      tab4t(:,:,7),tab4t(:,:,8) ) 
     347                                     tab4t(:,:,7),tab4t(:,:,8),         & 
     348                                     tab5t(:,:,1),tab5t(:,:,2)) 
    322349    endif 
    323350 
  • branches/2017/dev_r8126_UKMO_AGRIF_vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modmpp.F90

    r5656 r8138  
    166166subroutine Get_External_Data_first ( pttruetab, cetruetab, pttruetabwhole, cetruetabwhole,  & 
    167167                                     nbdim, memberoutall, coords, sendtoproc, recvfromproc, & 
    168                                      imin, imax, imin_recv, imax_recv ) 
     168                                     imin, imax, imin_recv, imax_recv, bornesmin, bornesmax ) 
    169169!--------------------------------------------------------------------------------------------------- 
    170170    include 'mpif.h' 
     
    179179    integer, dimension(nbdim,0:Agrif_NbProcs-1), intent(out) :: imin,imax 
    180180    integer, dimension(nbdim,0:Agrif_NbProcs-1), intent(out) :: imin_recv,imax_recv 
     181    integer, dimension(nbdim,0:Agrif_NbProcs-1), intent(in) :: bornesmin, bornesmax 
    181182! 
    182183    integer :: imintmp, imaxtmp, i, j, k, i1 
     
    211212            IF (cetruetab(i,Agrif_Procrank) > cetruetab(i,k)) THEN 
    212213                DO j=imin1,imax1 
    213                     IF ((cetruetab(i,k)-j) > (j-pttruetab(i,Agrif_Procrank))) THEN 
     214                    IF ((bornesmax(i,k)-j) > (j-bornesmin(i,Agrif_Procrank))) THEN 
    214215                        imintmp = j+1 
    215216                        tochange = .TRUE. 
     
    228229            IF (pttruetab(i,Agrif_Procrank) < pttruetab(i,k)) THEN 
    229230                DO j=imax1,imin1,-1 
    230                     IF ((j-pttruetab(i,k)) > (cetruetab(i,Agrif_Procrank)-j)) THEN 
     231                    IF ((j-bornesmin(i,k)) > (bornesmax(i,Agrif_Procrank)-j)) THEN 
    231232                        imaxtmp = j-1 
    232233                        tochange = .TRUE. 
  • branches/2017/dev_r8126_UKMO_AGRIF_vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modtypes.F90

    r5656 r8138  
    109109    real(4), dimension(:,:,:,:,:,:), allocatable :: sarray6 
    110110!> @} 
     111!> \name Arrays containing the values of the grid variables (real) 
     112!> @{ 
     113    real,    dimension(:)          , pointer :: parray1 
     114    real,    dimension(:,:)        , pointer :: parray2 
     115    real,    dimension(:,:,:)      , pointer :: parray3 
     116    real,    dimension(:,:,:,:)    , pointer :: parray4 
     117    real,    dimension(:,:,:,:,:)  , pointer :: parray5 
     118    real,    dimension(:,:,:,:,:,:), pointer :: parray6 
     119!> @} 
     120!> \name Arrays containing the values of the grid variables (real*8) 
     121!> @{ 
     122    real(8), dimension(:)          , pointer :: pdarray1 
     123    real(8), dimension(:,:)        , pointer :: pdarray2 
     124    real(8), dimension(:,:,:)      , pointer :: pdarray3 
     125    real(8), dimension(:,:,:,:)    , pointer :: pdarray4 
     126    real(8), dimension(:,:,:,:,:)  , pointer :: pdarray5 
     127    real(8), dimension(:,:,:,:,:,:), pointer :: pdarray6 
     128!> @} 
     129!> \name Arrays containing the values of the grid variables (real*4) 
     130!> @{ 
     131    real(4), dimension(:)          , pointer :: psarray1 
     132    real(4), dimension(:,:)        , pointer :: psarray2 
     133    real(4), dimension(:,:,:)      , pointer :: psarray3 
     134    real(4), dimension(:,:,:,:)    , pointer :: psarray4 
     135    real(4), dimension(:,:,:,:,:)  , pointer :: psarray5 
     136    real(4), dimension(:,:,:,:,:,:), pointer :: psarray6 
     137!> @} 
    111138!> \name Arrays used to restore the values 
    112139!> @{ 
     
    153180!> \name Arrays containing the values of the grid variables (character) 
    154181!> @{ 
    155     character(2400)                             :: carray0 
    156     character(200), dimension(:)  , allocatable :: carray1 
    157     character(200), dimension(:,:), allocatable :: carray2 
     182    character(4000)                             :: carray0 
     183    character(400), dimension(:)  , allocatable :: carray1 
     184    character(400), dimension(:,:), allocatable :: carray2 
    158185!> @} 
    159186!--------------------------------------------------------------------------------------------------- 
     
    218245!> \name Arrays containing the values of the grid variables (logical) 
    219246!> @{ 
    220     logical                                      :: larray0 
     247    logical                                      :: larray0 = .FALSE. 
    221248    logical, dimension(:)          , allocatable :: larray1 
    222249    logical, dimension(:,:)        , allocatable :: larray2 
     
    242269!> \name Arrays containing the values of the grid variables (integer) 
    243270!> @{ 
    244     integer                                      :: iarray0 
     271    integer                                      :: iarray0 = 0 
    245272    integer, dimension(:)          , allocatable :: iarray1 
    246273    integer, dimension(:,:)        , allocatable :: iarray2 
  • branches/2017/dev_r8126_UKMO_AGRIF_vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modupdate.F90

    r5656 r8138  
    582582                                     nbdim, memberinall, coords,                            & 
    583583                                     sendtoproc1,recvfromproc1,                             & 
    584                                      tab4t(:,:,5),tab4t(:,:,6),tab4t(:,:,7),tab4t(:,:,8)) 
     584                                     tab4t(:,:,5),tab4t(:,:,6),tab4t(:,:,7),tab4t(:,:,8),   & 
     585                                     tab4t(:,:,1),tab4t(:,:,2)) 
    585586    endif 
    586587 
     
    11541155                                     nbdim, memberinall2, coords,                           & 
    11551156                                     sendtoproc2, recvfromproc2,                            & 
    1156                                      tab5t(:,:,5),tab5t(:,:,6),tab5t(:,:,7),tab5t(:,:,8)) 
     1157                                     tab5t(:,:,5),tab5t(:,:,6),tab5t(:,:,7),tab5t(:,:,8),   & 
     1158                                     tab5t(:,:,1),tab5t(:,:,2)) 
    11571159 
    11581160        call Agrif_Addto_list_update(child%list_update,pttab,petab,lb_child,lb_parent,      & 
  • branches/2017/dev_r8126_UKMO_AGRIF_vert_interp/NEMOGCM/EXTERNAL/AGRIF/AGRIF_FILES/modutil.F90

    r5656 r8138  
    108108!--------------------------------------------------------------------------------------------------- 
    109109end subroutine Agrif_Step_Child 
     110!=================================================================================================== 
     111! 
     112!=================================================================================================== 
     113!  subroutine Agrif_Step_Childs 
     114! 
     115!> Apply 'procname' to each child grids of the current grid 
     116!--------------------------------------------------------------------------------------------------- 
     117!     ************************************************************************** 
     118!!!   Subroutine Agrif_Step_Childs 
     119!     ************************************************************************** 
     120! 
     121      Subroutine Agrif_Step_Childs(procname) 
     122! 
     123    procedure(step_proc)    :: procname     !< subroutine to call on each grid 
     124!     Pointer argument 
     125      Type(Agrif_Grid),pointer   :: g        ! Pointer on the current grid 
     126! 
     127 
     128! 
     129!     Local pointer 
     130      Type(Agrif_pgrid),pointer  :: parcours ! Pointer for the recursive 
     131                                             ! procedure 
     132! 
     133      g => Agrif_Curgrid 
     134       
     135      parcours => g % child_list % first 
     136! 
     137!     Recursive procedure for the time integration of the grid hierarchy       
     138      Do while (associated(parcours)) 
     139! 
     140!       Instanciation of the variables of the current grid 
     141        Call Agrif_Instance(parcours % gr) 
     142 
     143!     One step on the current grid 
     144 
     145         Call procname () 
     146        parcours => parcours % next 
     147      enddo 
     148    
     149      If (associated(g % child_list % first)) Call Agrif_Instance (g) 
     150      Return 
     151      End Subroutine Agrif_Step_Childs 
    110152!=================================================================================================== 
    111153! 
Note: See TracChangeset for help on using the changeset viewer.