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.
moduserfunctions.F90 in vendors/AGRIF/CMEMS_2020/AGRIF_FILES – NEMO

source: vendors/AGRIF/CMEMS_2020/AGRIF_FILES/moduserfunctions.F90 @ 10087

Last change on this file since 10087 was 10087, checked in by rblod, 6 years ago

update AGRIF library

File size: 65.8 KB
Line 
1!
2! $Id: modcurgridfunctions.F 774 2007-12-18 16:45:53Z rblod $
3!
4!     AGRIF (Adaptive Grid Refinement In Fortran)
5!
6!     Copyright (C) 2003 Laurent Debreu (Laurent.Debreu@imag.fr)
7!                        Christophe Vouland (Christophe.Vouland@imag.fr)
8!
9!     This program is free software; you can redistribute it and/or modify
10!     it under the terms of the GNU General Public License as published by
11!     the Free Software Foundation; either version 2 of the License, or
12!     (at your option) any later version.
13!
14!     This program is distributed in the hope that it will be useful,
15!     but WITHOUT ANY WARRANTY; without even the implied warranty of
16!     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
17!     GNU General Public License for more details.
18!
19!     You should have received a copy of the GNU General Public License
20!     along with this program; if not, write to the Free Software
21!     Foundation, Inc., 59 Temple Place-  Suite 330, Boston, MA 02111-1307, USA.
22!
23!-------------------------------------------------------------------------------
24!> Module Agrif_user_Functions
25!!
26!! This module defines procedures concerning current grids informations.
27!-------------------------------------------------------------------------------
28!
29module Agrif_User_Functions
30!
31! Module used:
32  use Agrif_Init
33  use Agrif_Grids
34!
35    implicit none
36!
37
38    interface Agrif_Parent
39        module procedure Agrif_Parent_Real_4,   &
40                         Agrif_Parent_Real_8,   &
41                         Agrif_Parent_Integer, &
42                         Agrif_Parent_Character, &
43                         Agrif_Parent_Logical
44    end interface
45
46    interface Agrif_Set_Parent
47        module procedure Agrif_Set_Parent_int,      &
48                         Agrif_Set_Parent_real4,    &
49                         Agrif_Set_Parent_real8
50    end interface
51   
52contains
53!
54!===================================================================================================
55!  subroutine Agrif_Set_parent_int
56!
57!> This subroutine is used to set the type of the variable of the parent grid of the
58!! current grid as integer variable.
59!
60!---------------------------------------------------------------------------------------------------
61subroutine Agrif_Set_parent_int(integer_variable,value)
62!---------------------------------------------------------------------------------------------------
63    integer, intent(in)     :: integer_variable !< indice of the variable in tabvars
64    integer, intent(in)     :: value        !< input value
65!
66   
67integer :: i
68logical :: i_found
69
70i_found = .FALSE.
71
72do i=1,Agrif_NbVariables(4)
73  if (LOC(integer_variable) == LOC(agrif_curgrid%tabvars_i(i)%iarray0)) then
74     agrif_curgrid%tabvars_i(i)%parent_var%iarray0 = value
75     i_found = .TRUE.
76     EXIT
77  endif
78enddo
79
80if (.NOT.i_found) STOP 'Agrif_Set_Integer : Variable not found'
81
82!---------------------------------------------------------------------------------------------------
83end subroutine Agrif_Set_parent_int
84!===================================================================================================
85!
86!===================================================================================================
87!  subroutine Agrif_Set_parent_real4
88!---------------------------------------------------------------------------------------------------
89!> This subroutine is used to set a real variable of the parent grid of the current
90!! grid as Single-precision real floating-point value.
91!
92!---------------------------------------------------------------------------------------------------
93subroutine Agrif_Set_parent_real4 ( real_variable, value )
94!---------------------------------------------------------------------------------------------------
95    real(kind=4), intent(in)     :: real_variable !< input variable
96    real(kind=4),intent(in) :: value        !< input value for the parent grid
97
98integer :: i
99logical :: i_found
100
101i_found = .FALSE.
102
103do i=1,Agrif_NbVariables(2)
104  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%array0)) then
105     agrif_curgrid%tabvars_r(i)%parent_var%array0 = value
106     agrif_curgrid%tabvars_r(i)%parent_var%sarray0 = value
107     i_found = .TRUE.
108     EXIT
109  endif
110enddo
111
112IF (.NOT.i_found) THEN
113do i=1,Agrif_NbVariables(2)
114  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%sarray0)) then
115     agrif_curgrid%tabvars_r(i)%parent_var%array0 = value
116     agrif_curgrid%tabvars_r(i)%parent_var%sarray0 = value
117     i_found = .TRUE.
118     EXIT
119  endif
120enddo
121ENDIF
122
123if (.NOT.i_found) STOP 'Agrif_Set_parent_real4 : Variable not found'
124
125!---------------------------------------------------------------------------------------------------
126end subroutine Agrif_Set_parent_real4
127!===================================================================================================
128!
129!===================================================================================================
130!  subroutine Agrif_Set_parent_real8
131!---------------------------------------------------------------------------------------------------
132!> This subroutine is used to set a real variable of the parent grid of the current
133!! grid as Double-precision real floating-point value.
134!
135!---------------------------------------------------------------------------------------------------
136subroutine Agrif_Set_parent_real8 ( real_variable, value )
137!---------------------------------------------------------------------------------------------------
138    real(kind=8), intent(in)     :: real_variable !< input variable
139    real(kind=8),intent(in) :: value        !< input value for the parent grid
140
141integer :: i
142logical :: i_found
143
144i_found = .FALSE.
145
146do i=1,Agrif_NbVariables(2)
147  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%array0)) then
148     agrif_curgrid%tabvars_r(i)%parent_var%darray0 = value
149     agrif_curgrid%tabvars_r(i)%parent_var%array0 = value
150     i_found = .TRUE.
151     EXIT
152  endif
153enddo
154
155IF (.NOT.i_found) THEN
156do i=1,Agrif_NbVariables(2)
157  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%darray0)) then
158     agrif_curgrid%tabvars_r(i)%parent_var%darray0 = value
159     agrif_curgrid%tabvars_r(i)%parent_var%array0 = value
160     i_found = .TRUE.
161     EXIT
162  endif
163enddo
164ENDIF
165
166if (.NOT.i_found) STOP 'Agrif_Set_parent_real8 : Variable not found'
167
168!---------------------------------------------------------------------------------------------------
169end subroutine Agrif_Set_parent_real8
170!===================================================================================================
171!
172!
173!===================================================================================================
174!  Function Agrif_rel_dt
175!
176!> Returns the time step of the current grid, relatively to the root grid (for which dt=1.).
177!!
178!! In fact, it is a real number which could be define as the ratio between the current grid time
179!!step and the root grid time step.
180!---------------------------------------------------------------------------------------------------
181function Agrif_rel_dt ( ) result( rel_dt )
182!---------------------------------------------------------------------------------------------------
183    integer :: i
184    real    :: rel_dt !< time step
185!
186    rel_dt = 1.
187!
188    do i = 1,Agrif_Probdim
189        rel_dt = min(rel_dt, Agrif_Curgrid % Agrif_dt(i))
190    enddo
191!---------------------------------------------------------------------------------------------------
192end function Agrif_rel_dt
193!===================================================================================================
194!
195!===================================================================================================
196!  function Agrif_rel_idt
197!
198!> This function returns an integer which is the time refinement factor of the current grid,
199!! relatively to the root grid (for which time step = 1).
200!!
201!! It is the inverse of Agrif_rel_dt set to integer. Here, it is the ratio between the time step
202!! of the root grid and the time step of the current grid.
203!---------------------------------------------------------------------------------------------------
204function Agrif_rel_idt ( ) result( rel_idt )
205!---------------------------------------------------------------------------------------------------
206    integer :: rel_idt !< time step
207!
208    rel_idt = nint(1./Agrif_rel_dt())
209!---------------------------------------------------------------------------------------------------
210end function Agrif_rel_idt
211!===================================================================================================
212!
213!===================================================================================================
214!  function Agrif_IRhot
215!
216!> This function returns an integer number which is the time refinement factor of the current grid.
217!---------------------------------------------------------------------------------------------------
218function Agrif_IRhot ( ) result( irhot )
219!---------------------------------------------------------------------------------------------------
220    integer :: i
221    integer :: irhot !< time refinement factor of the current grid
222!
223    irhot = 1
224!
225    do i = 1,Agrif_Probdim
226        irhot = max(irhot, Agrif_Curgrid % timeref(i))
227    enddo
228!---------------------------------------------------------------------------------------------------
229end function Agrif_IRhot
230!===================================================================================================
231!
232!===================================================================================================
233!  function Agrif_Rhot
234!
235!> This function returns a real number which is the time refinement factor of the current grid.
236!---------------------------------------------------------------------------------------------------
237function Agrif_Rhot ( ) result( rhot )
238!---------------------------------------------------------------------------------------------------
239    real    :: rhot !< time refinement factor of the current grid
240!
241    rhot = float(Agrif_IRhot())
242!---------------------------------------------------------------------------------------------------
243end function Agrif_Rhot
244!===================================================================================================
245!
246!===================================================================================================
247!  function Agrif_Parent_IRhot
248!
249!> This function returns an integer number which represents the time refinement factor of the parent of the current grid.
250!---------------------------------------------------------------------------------------------------
251function Agrif_Parent_IRhot ( ) result( irhot )
252!---------------------------------------------------------------------------------------------------
253    integer :: i
254    integer :: irhot !< time refinement factor of the parent grid
255!
256    irhot = 1
257!
258    do i = 1,Agrif_Probdim
259        irhot = max(irhot, Agrif_Curgrid % parent % timeref(i))
260    enddo
261!---------------------------------------------------------------------------------------------------
262end function Agrif_Parent_IRhot
263!===================================================================================================
264!
265!===================================================================================================
266!  function Agrif_Parent_Rhot
267!
268!> Returns a real number which represents the time refinement factor of the parent of the current grid.
269!---------------------------------------------------------------------------------------------------
270function Agrif_Parent_Rhot ( ) result( rhot )
271!---------------------------------------------------------------------------------------------------
272    real :: rhot !< time refinement factor of the parent grid
273!
274    rhot = float(Agrif_Parent_IRhot())
275!---------------------------------------------------------------------------------------------------
276end function Agrif_Parent_Rhot
277!===================================================================================================
278!
279!===================================================================================================
280!  Function Agrif_Nbstepint
281!
282!> This function returns an integer which is the time step of the current grid inside one time
283!! step of its parent grid.
284!!
285!! It variates from zero to the time refinement factor of the current grid minus 1 (Agrif_Rhot - 1).
286!! It is useful for example for interpolation/update.
287!
288!---------------------------------------------------------------------------------------------------
289function Agrif_Nbstepint ( )
290!---------------------------------------------------------------------------------------------------
291    integer :: Agrif_nbstepint !< time step of the current grid
292!
293    Agrif_nbstepint = mod(Agrif_Curgrid % ngridstep, Agrif_iRhot())
294!---------------------------------------------------------------------------------------------------
295end function Agrif_Nbstepint
296!===================================================================================================
297!
298!===================================================================================================
299!  function Agrif_Parent_Nbstepint
300!
301!> It returns an integer which represents time step of the parent grid inside one time step of its
302!! parent grid.
303!!
304!! It variates from zero to the time refinement factor of the parent grid minus 1 (Agrif_Parent_Rhot - 1).
305!---------------------------------------------------------------------------------------------------
306function Agrif_Parent_Nbstepint ( )
307!---------------------------------------------------------------------------------------------------
308    integer :: Agrif_Parent_Nbstepint !< time step of the parent grid
309!
310    Agrif_Parent_Nbstepint = mod(Agrif_Curgrid % parent % ngridstep, int(Agrif_Parent_Rhot()))
311!---------------------------------------------------------------------------------------------------
312end function Agrif_Parent_Nbstepint
313!===================================================================================================
314!
315!===================================================================================================
316!  subroutine Agrif_InterpNearBorderX
317!
318!> Allows to interpolate (in the x direction) on a near (West) border of the current grid if this one
319!! has a common border with the root coarse grid.
320!---------------------------------------------------------------------------------------------------
321subroutine Agrif_InterpNearBorderX ( )
322!---------------------------------------------------------------------------------------------------
323    Agrif_Curgrid % NearRootBorder(1) = .FALSE.
324!---------------------------------------------------------------------------------------------------
325end subroutine Agrif_InterpNearBorderX
326!===================================================================================================
327!
328!===================================================================================================
329!  subroutine Agrif_InterpDistantBorderX
330!
331!> Allows to interpolate (in the x direction) on a distant (East) border of the current grid if this one
332!! has a common border with the root coarse grid.
333!---------------------------------------------------------------------------------------------------
334subroutine Agrif_InterpDistantBorderX ( )
335!---------------------------------------------------------------------------------------------------
336    Agrif_Curgrid % DistantRootBorder(1) = .FALSE.
337!---------------------------------------------------------------------------------------------------
338end subroutine Agrif_InterpDistantBorderX
339!===================================================================================================
340!
341!===================================================================================================
342!  subroutine Agrif_InterpNearBorderY
343!
344!> Allows to interpolate (in the y direction) on a near (South) border of the current grid if this one
345!! has a common border with the root coarse grid.
346!---------------------------------------------------------------------------------------------------
347subroutine Agrif_InterpNearBorderY ( )
348!---------------------------------------------------------------------------------------------------
349    Agrif_Curgrid % NearRootBorder(2) = .FALSE.
350!---------------------------------------------------------------------------------------------------
351end subroutine Agrif_InterpNearBorderY
352!===================================================================================================
353!
354!===================================================================================================
355!  subroutine Agrif_InterpDistantBorderY
356!
357!> Allows to interpolate (in the y direction) on a distant (North) border of the current grid if this one
358!! has a common border with the root coarse grid.
359!---------------------------------------------------------------------------------------------------
360subroutine Agrif_InterpDistantBorderY ( )
361!---------------------------------------------------------------------------------------------------
362    Agrif_Curgrid % DistantRootBorder(2) = .FALSE.
363!---------------------------------------------------------------------------------------------------
364end subroutine Agrif_InterpDistantBorderY
365!===================================================================================================
366!
367!===================================================================================================
368!  subroutine Agrif_InterpNearBorderZ
369!
370!> Allows to interpolate (in the z direction) on a near (Down) border of the current grid if this one
371!! has a common border with the root coarse grid.
372!---------------------------------------------------------------------------------------------------
373subroutine Agrif_InterpNearBorderZ ( )
374!---------------------------------------------------------------------------------------------------
375    Agrif_Curgrid % NearRootBorder(3) = .FALSE.
376!---------------------------------------------------------------------------------------------------
377end subroutine Agrif_InterpNearBorderZ
378!===================================================================================================
379!
380!===================================================================================================
381!  subroutine Agrif_InterpDistantBorderZ
382!
383!> Allows to interpolate (in the z direction) on a distant (Up) border of the current grid if this one
384!! has a common border with the root coarse grid.
385!---------------------------------------------------------------------------------------------------
386subroutine Agrif_InterpDistantBorderZ()
387!---------------------------------------------------------------------------------------------------
388    Agrif_Curgrid % DistantRootBorder(3) = .FALSE.
389!---------------------------------------------------------------------------------------------------
390end subroutine Agrif_InterpDistantBorderZ
391!===================================================================================================
392!
393!===================================================================================================
394!  function Agrif_Parent_Nb_Step
395!
396!> This function returns an integer which is the number of time step of the parent of the current grid.
397!!
398!! In fact, it indicates the number of iterations done on the parent grid of the current grid
399!! since the start of the time integration of the grid.
400!---------------------------------------------------------------------------------------------------
401function Agrif_Parent_Nb_Step ( )
402!---------------------------------------------------------------------------------------------------
403    integer :: Agrif_Parent_Nb_Step !< time step of the parent of the current grid
404!
405    if (Agrif_Root()) then
406        Agrif_Parent_Nb_Step = -1
407    else
408        Agrif_Parent_Nb_Step = Agrif_Curgrid % parent % ngridstep
409    endif
410!---------------------------------------------------------------------------------------------------
411end function Agrif_Parent_Nb_Step
412!===================================================================================================
413!
414!===================================================================================================
415!  Function Agrif_Root
416!
417!> This function returns a logical which indicates if the current grid is the root grid or not.
418!---------------------------------------------------------------------------------------------------
419function Agrif_Root ( )
420!---------------------------------------------------------------------------------------------------
421    logical :: Agrif_Root !  Result
422!
423    Agrif_Root = (Agrif_Curgrid % fixedrank == 0)
424!---------------------------------------------------------------------------------------------------
425end function Agrif_Root
426!===================================================================================================
427!
428!===================================================================================================
429!  function Agrif_GrandMother
430!
431!> This function returns a logical which indicates if the current grid is the grandmother grid or not.
432!---------------------------------------------------------------------------------------------------
433function Agrif_GrandMother ( )
434!---------------------------------------------------------------------------------------------------
435    logical :: Agrif_GrandMother ! Result
436!
437    Agrif_GrandMother = Agrif_Curgrid % grand_mother_grid
438!---------------------------------------------------------------------------------------------------
439end function Agrif_GrandMother
440!===================================================================================================
441!
442!===================================================================================================
443!  function Agrif_Parent_Root
444!
445!> This function indicates if the parent of the current grid is the root grid or not.
446!---------------------------------------------------------------------------------------------------
447function Agrif_Parent_Root ( )
448!---------------------------------------------------------------------------------------------------
449    logical :: Agrif_Parent_Root ! Result
450!
451    Agrif_Parent_Root = (Agrif_Curgrid % parent % fixedrank == 0)
452!---------------------------------------------------------------------------------------------------
453end function Agrif_Parent_Root
454!===================================================================================================
455!
456!===================================================================================================
457!  function Agrif_Fixed
458!
459!> This function returns the number of the current grid.
460!!
461!!Indeed, it returns 0 for the coarse grid, a positive number for a fixed grid and -1 for a non fixed grid.
462!---------------------------------------------------------------------------------------------------
463function Agrif_Fixed ( )
464!---------------------------------------------------------------------------------------------------
465    integer :: Agrif_Fixed   !< Result
466!
467    if (Agrif_Curgrid % fixed) then
468        Agrif_Fixed = Agrif_Curgrid % fixedrank
469    else
470        Agrif_Fixed = -1
471    endif
472!---------------------------------------------------------------------------------------------------
473end function Agrif_Fixed
474!===================================================================================================
475!
476!===================================================================================================
477!  function Agrif_Parent_Fixed
478!
479!> This function returns the number of the parent of the current grid.
480!!
481!!Indeed, it returns 0 for the coarse grid and non fixed parent grid and positive number for a fixed grid.
482!---------------------------------------------------------------------------------------------------
483function Agrif_Parent_Fixed ( )
484!---------------------------------------------------------------------------------------------------
485    integer :: Agrif_Parent_Fixed   ! Result
486!
487    if (Agrif_Curgrid % parent % fixed) then
488        Agrif_Parent_Fixed = Agrif_Curgrid % parent % fixedrank
489    else
490        Agrif_Parent_Fixed = 0
491    endif
492!---------------------------------------------------------------------------------------------------
493end function Agrif_Parent_Fixed
494!===================================================================================================
495!
496!===================================================================================================
497!  function Agrif_Is_Fixed
498!
499!> This function returns .TRUE. if the current grid is fixed even if we are on the root grid.
500!---------------------------------------------------------------------------------------------------
501function Agrif_Is_Fixed ( )
502!---------------------------------------------------------------------------------------------------
503    logical :: Agrif_Is_Fixed   ! Result
504!
505    Agrif_Is_Fixed = Agrif_Curgrid % fixed
506!---------------------------------------------------------------------------------------------------
507end function Agrif_Is_Fixed
508!===================================================================================================
509!
510!===================================================================================================
511!  function Agrif_Parent_Is_Fixed
512!
513!> This function returns .TRUE. if the parent grid of the current grid is fixed even if we are on the root grid.
514!---------------------------------------------------------------------------------------------------
515function Agrif_Parent_Is_Fixed ( )
516!---------------------------------------------------------------------------------------------------
517    logical :: Agrif_Parent_Is_Fixed   ! Result
518!
519    Agrif_Parent_Is_Fixed = Agrif_Curgrid % parent % fixed
520!---------------------------------------------------------------------------------------------------
521end function Agrif_Parent_Is_Fixed
522!===================================================================================================
523!
524!===================================================================================================
525!  function Agrif_CFixed
526!
527!> This function returns the number of the current grid as a string.
528!---------------------------------------------------------------------------------------------------
529function Agrif_CFixed ( )
530!---------------------------------------------------------------------------------------------------
531    character(3) :: Agrif_CFixed   ! Result
532!
533    character(3) :: cfixed
534    integer      :: fixed
535!
536    fixed = Agrif_Fixed()
537!
538    if (fixed /= -1) then
539!
540        if (fixed <= 9) then
541            write(cfixed,'(i1)') fixed
542        else
543            write(cfixed,'(i2)') fixed
544        endif
545!
546        Agrif_CFixed = cfixed
547       
548        if (associated(agrif_curgrid,agrif_coarsegrid)) then
549          Agrif_CFixed = 'gm'
550        endif
551!
552    else
553        print*,'Call to Agrif_CFixed() on a moving grid'
554        stop
555    endif
556!---------------------------------------------------------------------------------------------------
557end function Agrif_CFixed
558!===================================================================================================
559!
560!===================================================================================================
561!  function Agrif_Parent_CFixed
562!
563!> This function returns the number of the parent of the current grid as a string.
564!---------------------------------------------------------------------------------------------------
565function Agrif_Parent_CFixed ( )
566!---------------------------------------------------------------------------------------------------
567    character(3) :: Agrif_Parent_CFixed   ! Result
568!
569    character(3) :: cfixed
570    integer      :: fixed
571!
572    fixed = Agrif_Parent_Fixed()
573!
574    if(fixed /= -1) then
575!
576        if (fixed <= 9) then
577            write(cfixed,'(i1)')fixed
578        else
579            write(cfixed,'(i2)')fixed
580        endif
581!
582        Agrif_Parent_CFixed=cfixed
583!
584    else
585        print*,'Illegal call to Agrif_Parent_CFixed()'
586        stop
587    endif
588!---------------------------------------------------------------------------------------------------
589end function Agrif_Parent_CFixed
590!===================================================================================================
591!
592!===================================================================================================
593!  subroutine Agrif_ChildGrid_to_ParentGrid
594!
595!> This subroutine makes #Agrif_Curgrid point on the parent grid of the current grid.
596!---------------------------------------------------------------------------------------------------
597subroutine Agrif_ChildGrid_to_ParentGrid ( )
598!---------------------------------------------------------------------------------------------------
599    Agrif_Curgrid % parent % save_grid => Agrif_Curgrid
600    call Agrif_Instance(Agrif_Curgrid%parent)
601!---------------------------------------------------------------------------------------------------
602end subroutine Agrif_ChildGrid_to_ParentGrid
603!===================================================================================================
604!
605!===================================================================================================
606!  subroutine Agrif_ParentGrid_to_ChildGrid
607!
608!> This subroutine makes the pointer #Agrif_Curgrid point on the child grid after having called the subroutine
609!! :agrifdoc:`moduserfunctions.F90::agrif_childgrid_to_parentgrid<Agrif_ChildGrid_to_ParentGrid()>` .
610!---------------------------------------------------------------------------------------------------
611subroutine Agrif_ParentGrid_to_ChildGrid ( )
612!---------------------------------------------------------------------------------------------------
613    call Agrif_Instance(Agrif_Curgrid%save_grid)
614!---------------------------------------------------------------------------------------------------
615end subroutine Agrif_ParentGrid_to_ChildGrid
616!===================================================================================================
617!
618!===================================================================================================
619!  function Agrif_Get_Unit
620!
621!> This function returns a unit not connected to any file.
622!---------------------------------------------------------------------------------------------------
623function Agrif_Get_Unit ( )
624!---------------------------------------------------------------------------------------------------
625    integer :: Agrif_Get_Unit  ! Result
626!
627    integer :: n
628    logical :: op
629!
630    integer :: nunit
631    integer :: iii, out, iiimax
632    logical :: bexist
633    integer,dimension(1:1000) :: forbiddenunit
634!
635!   Load forbidden Unit if the file Agrif_forbidenUnit exist
636!
637    INQUIRE(file='Agrif_forbiddenUnit.txt', exist=bexist)
638!
639    if (.not. bexist) then
640!       File Agrif_forbiddenUnit.txt not found
641    else
642        nunit = 777
643        OPEN(nunit,file='Agrif_forbiddenUnit.txt', form='formatted', status="old")
644        iii = 1
645        do while ( .TRUE. )
646            READ(nunit,*, end=99) forbiddenunit(iii)
647            iii = iii + 1
648        enddo
649   99   continue
650        iiimax = iii
651        close(nunit)
652    endif
653!
654    do n = 7,1000
655!
656        INQUIRE(Unit=n,Opened=op)
657!
658        out = 0
659        if ( bexist .AND. (.NOT.op) ) then
660            do iii = 1,iiimax
661                if ( n == forbiddenunit(iii) ) out = 1
662            enddo
663        endif
664!
665        if ( (.NOT.op) .AND. (out == 0) ) exit
666!
667    enddo
668!
669    Agrif_Get_Unit = n
670!---------------------------------------------------------------------------------------------------
671end function Agrif_Get_Unit
672!===================================================================================================
673!
674!===================================================================================================
675!  subroutine Agrif_Set_Extra_Boundary_Cells
676!> This subroutine is used to set the number of extra boundary cells which is take as input parameter.
677!---------------------------------------------------------------------------------------------------
678subroutine Agrif_Set_Extra_Boundary_Cells ( nb_extra_cells )
679!---------------------------------------------------------------------------------------------------
680    integer, intent(in) :: nb_extra_cells !< number of extra cells
681!
682    Agrif_Extra_Boundary_Cells = nb_extra_cells
683!---------------------------------------------------------------------------------------------------
684end subroutine Agrif_Set_Extra_Boundary_Cells
685!===================================================================================================
686!
687!===================================================================================================
688!  subroutine Agrif_Set_Efficiency
689!> This subroutine is used to set the efficiency which is taken as input parameter.
690!---------------------------------------------------------------------------------------------------
691subroutine Agrif_Set_Efficiency ( eff )
692!---------------------------------------------------------------------------------------------------
693    real, intent(in) :: eff !< efficiency
694!
695    if ( (eff < 0.) .OR. (eff > 1) ) then
696        write(*,*) 'Error Efficiency should be between 0 and 1'
697        stop
698    else
699        Agrif_Efficiency = eff
700    endif
701!---------------------------------------------------------------------------------------------------
702end subroutine Agrif_Set_Efficiency
703!===================================================================================================
704!
705!===================================================================================================
706!  subroutine Agrif_Set_Regridding
707!> This subroutine is used to set the regridding frequency which is taken as input parameter
708!---------------------------------------------------------------------------------------------------
709subroutine Agrif_Set_Regridding ( regfreq )
710!---------------------------------------------------------------------------------------------------
711    integer, intent(in) :: regfreq !< Regridding frequency
712!
713    if (regfreq < 0) then
714        write(*,*) 'Regridding frequency should be positive'
715        stop
716    else
717        Agrif_Regridding = regfreq
718    endif
719!---------------------------------------------------------------------------------------------------
720end subroutine Agrif_Set_Regridding
721!===================================================================================================
722!
723!===================================================================================================
724!  subroutine Agrif_Set_coeffref_x
725!> This subroutine is used to set the space refinement coefficient in the x direction (first dimension).
726!---------------------------------------------------------------------------------------------------
727subroutine Agrif_Set_coeffref_x ( coeffref )
728!---------------------------------------------------------------------------------------------------
729    integer, intent(in) :: coeffref !< Coefficient of spatial refinement
730
731      if (coeffref < 0) then
732         write(*,*) 'Coefficient of refinement should be positive'
733         stop
734      else
735         Agrif_coeffref(1) = coeffref
736      endif
737!---------------------------------------------------------------------------------------------------
738end subroutine Agrif_Set_coeffref_x
739!===================================================================================================
740!
741!===================================================================================================
742!  subroutine Agrif_Set_coeffref_y
743!> This subroutine is used to set the space refinement coefficient in the y direction (second dimension).
744!---------------------------------------------------------------------------------------------------
745subroutine Agrif_Set_coeffref_y ( coeffref )
746!---------------------------------------------------------------------------------------------------
747    integer, intent(in) :: coeffref !< Coefficient of spatial refinement
748
749    if (coeffref < 0) then
750        write(*,*) 'Coefficient of refinement should be positive'
751        stop
752    else
753        Agrif_coeffref(2) = coeffref
754    endif
755!---------------------------------------------------------------------------------------------------
756end subroutine Agrif_Set_coeffref_y
757!===================================================================================================
758!
759!===================================================================================================
760!  subroutine Agrif_Set_coeffref_z
761!> This subroutine is used to set the space refinement coefficient in the z direction (third dimension).
762!---------------------------------------------------------------------------------------------------
763subroutine Agrif_Set_coeffref_z ( coeffref )
764!---------------------------------------------------------------------------------------------------
765    integer, intent(in) :: coeffref !< Coefficient of spatial refinement
766!
767    if (coeffref < 0) then
768        write(*,*) 'Coefficient of refinement should be positive'
769        stop
770    else
771        Agrif_coeffref(3) = coeffref
772    endif
773!---------------------------------------------------------------------------------------------------
774end subroutine Agrif_Set_coeffref_z
775!===================================================================================================
776!
777!===================================================================================================
778!  subroutine Agrif_Set_coeffreft_x
779!> This subroutine is used to set the time refinement factor in x direction (first dimension).
780!---------------------------------------------------------------------------------------------------
781subroutine Agrif_Set_coeffreft_x ( coeffref )
782!---------------------------------------------------------------------------------------------------
783    integer, intent(in) :: coeffref !< Coefficient of time refinement
784
785    if (coeffref < 0) then
786        write(*,*) 'Coefficient of time refinement should be positive'
787        stop
788    else
789        Agrif_coeffreft(1) = coeffref
790    endif
791!---------------------------------------------------------------------------------------------------
792end subroutine Agrif_Set_coeffreft_x
793!===================================================================================================
794!
795!===================================================================================================
796!  subroutine Agrif_Set_coeffreft_y
797!> This subroutine is used to set the time refinement factor in y direction (second dimension).
798!---------------------------------------------------------------------------------------------------
799subroutine Agrif_Set_coeffreft_y ( coeffref )
800!---------------------------------------------------------------------------------------------------
801    integer, intent(in) :: coeffref !< Coefficient of time refinement
802!
803    if (coeffref < 0) then
804        write(*,*) 'Coefficient of time refinement should be positive'
805        stop
806    else
807        Agrif_coeffreft(2) = coeffref
808    endif
809!---------------------------------------------------------------------------------------------------
810end subroutine Agrif_Set_coeffreft_y
811!===================================================================================================
812!
813!===================================================================================================
814!  subroutine Agrif_Set_coeffreft_z
815!> This subroutine is used to set the time refinement coefficient in the z direction (third dimension).
816!---------------------------------------------------------------------------------------------------
817subroutine Agrif_Set_coeffreft_z ( coeffref )
818!---------------------------------------------------------------------------------------------------
819    integer, intent(in) :: coeffref
820
821    if (coeffref < 0) then
822        write(*,*)'Coefficient of time refinement should be positive'
823        stop
824    else
825        Agrif_coeffreft(3) = coeffref
826    endif
827!---------------------------------------------------------------------------------------------------
828end subroutine Agrif_Set_coeffreft_z
829!===================================================================================================
830!
831!===================================================================================================
832!  subroutine Agrif_Set_Minwidth
833!> This subroutine is used to set the minimum width which is taken as input parameter.
834!---------------------------------------------------------------------------------------------------
835subroutine Agrif_Set_Minwidth ( coefminwidth )
836!---------------------------------------------------------------------------------------------------
837    integer, intent(in) :: coefminwidth !< Coefficient of minwidth
838!
839    if (coefminwidth < 0) then
840        write(*,*)'Coefficient of Minwidth should be positive'
841        stop
842    else
843        Agrif_Minwidth = coefminwidth
844    endif
845!---------------------------------------------------------------------------------------------------
846end subroutine Agrif_Set_Minwidth
847!===================================================================================================
848!
849!===================================================================================================
850!  subroutine Agrif_Set_Rafmax
851!> This subroutine is used to set the maximal level in x,y and z-direction which is taken as input parameter.
852!---------------------------------------------------------------------------------------------------
853subroutine Agrif_Set_Rafmax ( coefrafmax )
854!---------------------------------------------------------------------------------------------------
855    integer, intent(in) :: coefrafmax !< maximal space refinement coefficient
856!
857    integer :: i
858    real    :: res
859!
860    if (coefrafmax < 0) then
861        write(*,*)'Refinement coefficient should be positive'
862        stop
863    else
864        res = 1.
865        do i = 1,coefrafmax-1
866            res = res * FLOAT(Agrif_coeffref(1))
867        enddo
868        if ( res == 0 ) res = 1
869        Agrif_Mind(1) = 1.d0 / real(res,kind=8)
870!
871        res = 1.
872        do i = 1,coefrafmax-1
873            res = res * FLOAT(Agrif_coeffref(2))
874        enddo
875        if ( res == 0 ) res = 1
876        Agrif_Mind(2) = 1.d0 / real(res,kind=8)
877!
878        res = 1.
879        do i = 1,coefrafmax-1
880            res = res * FLOAT(Agrif_coeffref(3))
881        enddo
882        if ( res == 0 ) res = 1
883        Agrif_Mind(3) = 1.d0 / real(res,kind=8)
884!
885      endif
886!---------------------------------------------------------------------------------------------------
887end subroutine Agrif_Set_Rafmax
888!===================================================================================================
889!
890!===================================================================================================
891!  subroutine Agrif_Set_MaskMaxSearch
892!---------------------------------------------------------------------------------------------------
893subroutine Agrif_Set_MaskMaxSearch ( mymaxsearch )
894!---------------------------------------------------------------------------------------------------
895    integer, intent(in) :: mymaxsearch !< input variables
896!
897    MaxSearch = mymaxsearch
898!---------------------------------------------------------------------------------------------------
899end subroutine Agrif_Set_MaskMaxSearch
900!===================================================================================================
901!
902!===================================================================================================
903!  function Agrif_Level
904!> This function returns the level of the current grid in the grids hierarchy.
905!---------------------------------------------------------------------------------------------------
906function Agrif_Level ( )
907!---------------------------------------------------------------------------------------------------
908    integer :: Agrif_Level  !< level of the current grid
909!
910    Agrif_Level = Agrif_Curgrid % level
911!---------------------------------------------------------------------------------------------------
912end function Agrif_Level
913!===================================================================================================
914!
915!===================================================================================================
916!  function Agrif_MaxLevel
917!> This function returns the maximum level of grid location in the hierarchy.
918!---------------------------------------------------------------------------------------------------
919function Agrif_MaxLevel ( )
920!---------------------------------------------------------------------------------------------------
921    integer :: Agrif_MaxLevel  ! Result
922!
923    Agrif_MaxLevel = Agrif_MaxLevelLoc
924!---------------------------------------------------------------------------------------------------
925end function Agrif_MaxLevel
926!===================================================================================================
927!
928!===================================================================================================
929!  function Agrif_GridAllocation_is_done
930!> This function is used to verify if the the allocation is done for the current grid.
931!---------------------------------------------------------------------------------------------------
932function Agrif_GridAllocation_is_done ( ) result(isdone)
933!---------------------------------------------------------------------------------------------------
934    logical :: isdone ! Result
935!
936    isdone = Agrif_Curgrid % allocation_is_done
937!---------------------------------------------------------------------------------------------------
938end function Agrif_GridAllocation_is_done
939!===================================================================================================
940!
941!===================================================================================================
942! function Agrif_Parent_Real_4
943!> This function returns the list of real grid variables of the parent of the current grid as single-precision
944!! real floating-point.
945!---------------------------------------------------------------------------------------------------
946function Agrif_Parent_Real_4(real_variable) result(real_variable_parent)
947!---------------------------------------------------------------------------------------------------
948real(KIND=4) :: real_variable !< input real variable
949real(KIND=4) :: real_variable_parent  ! Result
950
951integer :: i
952logical :: i_found
953
954i_found = .FALSE.
955
956do i=1,Agrif_NbVariables(2)
957  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%array0)) then
958     real_variable_parent = agrif_curgrid%tabvars_r(i)%parent_var%array0
959     i_found = .TRUE.
960     EXIT
961  endif
962enddo
963
964IF (.NOT.i_found) THEN
965do i=1,Agrif_NbVariables(2)
966  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%sarray0)) then
967     real_variable_parent = agrif_curgrid%tabvars_r(i)%parent_var%sarray0
968     i_found = .TRUE.
969     EXIT
970  endif
971enddo
972ENDIF
973
974if (.NOT.i_found) STOP 'Agrif_Parent_Real_4 : Variable not found'
975!---------------------------------------------------------------------------------------------------
976end function Agrif_Parent_Real_4
977!===================================================================================================
978!
979!===================================================================================================
980! function Agrif_Parent_Real_8
981!> This function returns the list of real grid variables of the parent of the current grid as double-precision
982!! real floating-point.
983!---------------------------------------------------------------------------------------------------
984function Agrif_Parent_Real_8(real_variable) result(real_variable_parent)
985!---------------------------------------------------------------------------------------------------
986real(KIND=8) :: real_variable !< input real variable
987real(KIND=8) :: real_variable_parent ! Result
988
989integer :: i
990logical :: i_found
991
992i_found = .FALSE.
993
994do i=1,Agrif_NbVariables(2)
995  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%array0)) then
996     real_variable_parent = agrif_curgrid%tabvars_r(i)%parent_var%array0
997     i_found = .TRUE.
998     EXIT
999  endif
1000enddo
1001
1002IF (.NOT.i_found) THEN
1003do i=1,Agrif_NbVariables(2)
1004  if (LOC(real_variable) == LOC(agrif_curgrid%tabvars_r(i)%darray0)) then
1005     real_variable_parent = agrif_curgrid%tabvars_r(i)%parent_var%darray0
1006     i_found = .TRUE.
1007     EXIT
1008  endif
1009enddo
1010ENDIF
1011
1012if (.NOT.i_found) STOP 'Agrif_Parent_Real_8 : Variable not found'
1013!---------------------------------------------------------------------------------------------------
1014end function Agrif_Parent_Real_8
1015!===================================================================================================
1016!
1017!===================================================================================================
1018! function Agrif_Parent_Integer
1019!> This function returns the list of integer grid variables of the parent of the current grid as integer.
1020!---------------------------------------------------------------------------------------------------
1021function Agrif_Parent_Integer(integer_variable) result(integer_variable_parent)
1022integer :: integer_variable
1023integer :: integer_variable_parent ! Result
1024
1025integer :: i
1026logical :: i_found
1027
1028i_found = .FALSE.
1029
1030do i=1,Agrif_NbVariables(4)
1031  if (LOC(integer_variable) == LOC(agrif_curgrid%tabvars_i(i)%iarray0)) then
1032     integer_variable_parent = agrif_curgrid%tabvars_i(i)%parent_var%iarray0
1033     i_found = .TRUE.
1034     EXIT
1035  endif
1036enddo
1037
1038if (.NOT.i_found) STOP 'Agrif_Parent : Variable not found'
1039!---------------------------------------------------------------------------------------------------
1040end function Agrif_Parent_Integer
1041!===================================================================================================
1042!
1043!===================================================================================================
1044! function Agrif_Parent_Character
1045!> This function returns the list of character grid variables of the parent of the current grid as character.
1046!---------------------------------------------------------------------------------------------------
1047function Agrif_Parent_Character(character_variable) result(character_variable_parent)
1048!---------------------------------------------------------------------------------------------------
1049character(*) :: character_variable
1050character(len(character_variable)) :: character_variable_parent ! Result
1051
1052integer :: i
1053logical :: i_found
1054
1055i_found = .FALSE.
1056
1057do i=1,Agrif_NbVariables(1)
1058  if (LOC(character_variable) == LOC(agrif_curgrid%tabvars_c(i)%carray0)) then
1059     character_variable_parent = agrif_curgrid%tabvars_c(i)%parent_var%carray0
1060     i_found = .TRUE.
1061     EXIT
1062  endif
1063enddo
1064
1065if (.NOT.i_found) STOP 'Agrif_Parent : Variable not found'
1066!---------------------------------------------------------------------------------------------------
1067end function Agrif_Parent_Character
1068!===================================================================================================
1069!
1070!===================================================================================================
1071! function Agrif_Parent_Logical
1072!> This function returns the list of logical grid variables of the parent of the current grid as logical variables.
1073!---------------------------------------------------------------------------------------------------
1074function Agrif_Parent_Logical(logical_variable) result(logical_variable_parent)
1075!---------------------------------------------------------------------------------------------------
1076logical :: logical_variable    !
1077logical :: logical_variable_parent   ! Result
1078
1079integer :: i
1080logical :: i_found
1081
1082i_found = .FALSE.
1083
1084do i=1,Agrif_NbVariables(3)
1085  if (LOC(logical_variable) == LOC(agrif_curgrid%tabvars_l(i)%larray0)) then
1086     logical_variable_parent = agrif_curgrid%tabvars_l(i)%parent_var%larray0
1087     i_found = .TRUE.
1088     EXIT
1089  endif
1090enddo
1091
1092if (.NOT.i_found) STOP 'Agrif_Parent : Variable not found'
1093!---------------------------------------------------------------------------------------------------
1094end function Agrif_Parent_Logical
1095!===================================================================================================
1096!
1097!===================================================================================================
1098! function Agrif_Irhox
1099!> This function is used to get the space refinement factor of the current grid in x direction (first dimension) set as integer.
1100!---------------------------------------------------------------------------------------------------
1101function Agrif_Irhox() result(i_val)
1102!---------------------------------------------------------------------------------------------------
1103integer :: i_val  ! Result
1104i_val = agrif_curgrid%spaceref(1)
1105!---------------------------------------------------------------------------------------------------
1106end function Agrif_Irhox
1107!===================================================================================================
1108!
1109!===================================================================================================
1110! function Agrif_Irhoy
1111!> This function is used to get the space refinement factor of the current grid in y direction (second dimension) set as integer.
1112!---------------------------------------------------------------------------------------------------
1113function Agrif_Irhoy() result(i_val)
1114!---------------------------------------------------------------------------------------------------
1115integer :: i_val  ! Result
1116i_val = agrif_curgrid%spaceref(2)
1117!---------------------------------------------------------------------------------------------------
1118end function Agrif_Irhoy
1119!===================================================================================================
1120!
1121!===================================================================================================
1122! function Agrif_Irhoz
1123!> This function is used to get the space refinement factor of the current grid in z direction (third dimension) set as integer.
1124!---------------------------------------------------------------------------------------------------
1125function Agrif_Irhoz() result(i_val)
1126!---------------------------------------------------------------------------------------------------
1127integer :: i_val  ! Result
1128i_val = agrif_curgrid%spaceref(3)
1129!---------------------------------------------------------------------------------------------------
1130end function Agrif_Irhoz
1131!===================================================================================================
1132!
1133!===================================================================================================
1134! function Agrif_NearCommonBorderX
1135!> This function returns a logical which indicates whether the current grid and root grid have a common
1136!! border on the western side of the first dimension of space (the x direction). 
1137!---------------------------------------------------------------------------------------------------
1138function Agrif_NearCommonBorderX() result(l_val)
1139!---------------------------------------------------------------------------------------------------
1140logical :: l_val  ! Result
1141l_val = agrif_curgrid%nearRootBorder(1)
1142!---------------------------------------------------------------------------------------------------
1143end function Agrif_NearCommonBorderX
1144!===================================================================================================
1145!
1146!===================================================================================================
1147! function Agrif_NearCommonBorderY
1148!> This function returns a logical which indicates whether the current grid and root grid have a common
1149!! border on the southern side of the second dimension of space (the y direction).
1150!---------------------------------------------------------------------------------------------------
1151function Agrif_NearCommonBorderY() result(l_val)
1152!---------------------------------------------------------------------------------------------------
1153logical :: l_val  ! Result
1154l_val = agrif_curgrid%nearRootBorder(2)
1155!---------------------------------------------------------------------------------------------------
1156end function Agrif_NearCommonBorderY
1157!===================================================================================================
1158!
1159!===================================================================================================
1160! function Agrif_NearCommonBorderZ
1161!> This function returns a logical which indicates whether the current grid and root grid have a common
1162!! border on the down side of the third dimension of space (the z direction).
1163!---------------------------------------------------------------------------------------------------
1164function Agrif_NearCommonBorderZ() result(l_val)
1165!---------------------------------------------------------------------------------------------------
1166logical :: l_val  ! Result
1167l_val = agrif_curgrid%nearRootBorder(3)
1168!---------------------------------------------------------------------------------------------------
1169end function Agrif_NearCommonBorderZ
1170!===================================================================================================
1171!
1172!===================================================================================================
1173! function Agrif_DistantCommonBorderX
1174!> This function returns a logical which indicates whether the current grid and root grid have a common
1175!! border on the eastern side of the first dimension of space (the x direction). 
1176!---------------------------------------------------------------------------------------------------
1177function Agrif_DistantCommonBorderX() result(l_val)
1178!---------------------------------------------------------------------------------------------------
1179logical :: l_val  ! Result
1180l_val = agrif_curgrid%DistantRootBorder(1)
1181!---------------------------------------------------------------------------------------------------
1182end function Agrif_DistantCommonBorderX
1183!===================================================================================================
1184!
1185!===================================================================================================
1186! function Agrif_DistantCommonBorderY
1187!> This function returns a logical which indicates whether the current grid and root grid have a common
1188!! border on the northern side of the second dimension of space (the y direction).
1189!---------------------------------------------------------------------------------------------------
1190function Agrif_DistantCommonBorderY() result(l_val)
1191!---------------------------------------------------------------------------------------------------
1192logical :: l_val  ! Result
1193l_val = agrif_curgrid%DistantRootBorder(2)
1194!---------------------------------------------------------------------------------------------------
1195end function Agrif_DistantCommonBorderY
1196!===================================================================================================
1197!
1198!===================================================================================================
1199! function Agrif_DistantCommonBorderZ
1200!> This function returns a logical which indicates whether the current grid and root grid have a common
1201!! border on the up side of the third dimension of space (the z direction).
1202!---------------------------------------------------------------------------------------------------
1203function Agrif_DistantCommonBorderZ() result(l_val)
1204!---------------------------------------------------------------------------------------------------
1205logical :: l_val  ! Result
1206l_val = agrif_curgrid%DistantRootBorder(3)
1207!---------------------------------------------------------------------------------------------------
1208end function Agrif_DistantCommonBorderZ
1209!===================================================================================================
1210!
1211!===================================================================================================
1212! function Agrif_Ix
1213!> This function returns an integer which indicates the minimal position of the current grid in the x direction.
1214!---------------------------------------------------------------------------------------------------
1215function Agrif_Ix() result(i_val)
1216!---------------------------------------------------------------------------------------------------
1217integer :: i_val  !< minimal position
1218i_val = agrif_curgrid%ix(1)
1219end function Agrif_Ix
1220!===================================================================================================
1221!
1222!===================================================================================================
1223! function Agrif_Iy
1224!> This function returns an integer which indicates the minimal position of the current grid in the y direction.
1225!---------------------------------------------------------------------------------------------------
1226function Agrif_Iy() result(i_val)
1227!---------------------------------------------------------------------------------------------------
1228integer :: i_val  !< minimal position
1229i_val = agrif_curgrid%ix(2)
1230end function Agrif_Iy
1231!===================================================================================================
1232!
1233!===================================================================================================
1234! function Agrif_Iz
1235!> This function returns an integer which indicates the minimal position of the current grid in the z direction.
1236!---------------------------------------------------------------------------------------------------
1237function Agrif_Iz() result(i_val)
1238!---------------------------------------------------------------------------------------------------
1239integer :: i_val !< minimal position
1240i_val = agrif_curgrid%ix(3)
1241!---------------------------------------------------------------------------------------------------
1242end function Agrif_Iz
1243!===================================================================================================
1244!
1245!===================================================================================================
1246! function Agrif_Get_grid_id
1247!> This function is used to get the grid id of the current grid.
1248!---------------------------------------------------------------------------------------------------
1249function Agrif_Get_grid_id() result(i_val)
1250!---------------------------------------------------------------------------------------------------
1251integer :: i_val !< grid id of the current grid
1252i_val = agrif_curgrid % grid_id
1253!---------------------------------------------------------------------------------------------------
1254end function Agrif_Get_grid_id
1255!===================================================================================================
1256!
1257!===================================================================================================
1258! function Agrif_Get_parent_id
1259!> This function is used to get the grid id of the parent grid of the current grid.
1260!---------------------------------------------------------------------------------------------------
1261function Agrif_Get_parent_id() result(i_val)
1262!---------------------------------------------------------------------------------------------------
1263integer :: i_val !< grid id of the parent grid
1264i_val = agrif_curgrid % parent % grid_id
1265!---------------------------------------------------------------------------------------------------
1266end function Agrif_Get_parent_id
1267!===================================================================================================
1268!
1269!===================================================================================================
1270! function Agrif_rhox
1271!> This function returns a real number which represents the space refinement factor of the current grid
1272!! for the first dimension x.
1273!---------------------------------------------------------------------------------------------------
1274function Agrif_rhox() result(r_val)
1275!---------------------------------------------------------------------------------------------------
1276real :: r_val !< space refinement factor
1277r_val = real(agrif_curgrid%spaceref(1))
1278!---------------------------------------------------------------------------------------------------
1279end function Agrif_rhox
1280!===================================================================================================
1281!
1282!===================================================================================================
1283! function Agrif_rhoy
1284!> This function returns a real number which represents the space refinement factor of the current grid
1285!! for the second dimension y.
1286!---------------------------------------------------------------------------------------------------
1287function Agrif_rhoy() result(r_val)
1288!---------------------------------------------------------------------------------------------------
1289real :: r_val !< space refinement factor
1290r_val = real(agrif_curgrid%spaceref(2))
1291!---------------------------------------------------------------------------------------------------
1292end function Agrif_rhoy
1293!===================================================================================================
1294!
1295!===================================================================================================
1296! function Agrif_rhoz
1297!> This function returns a real number which represents the space refinement factor of the current grid
1298!! for the third dimension z.
1299!---------------------------------------------------------------------------------------------------
1300function Agrif_rhoz() result(r_val)
1301!---------------------------------------------------------------------------------------------------
1302real :: r_val !< space refinement factor
1303r_val = real(agrif_curgrid%spaceref(3))
1304!---------------------------------------------------------------------------------------------------
1305end function Agrif_rhoz
1306!===================================================================================================
1307!
1308!===================================================================================================
1309! function Agrif_Nb_Step
1310!> This function returns an integer which represents the number of time steps of the current grid.
1311!---------------------------------------------------------------------------------------------------
1312function Agrif_Nb_Step() result(i_val)
1313!---------------------------------------------------------------------------------------------------
1314integer :: i_val !< number of time steps
1315i_val = agrif_curgrid%ngridstep
1316!---------------------------------------------------------------------------------------------------
1317end function Agrif_Nb_Step
1318!====================================================================================================
1319!
1320!===================================================================================================
1321! function Agrif_Nb_Fine_Grids
1322!> This function returns the number of fixed grids.
1323!---------------------------------------------------------------------------------------------------
1324function Agrif_Nb_Fine_Grids() result(i_val)
1325!--------------------------------------------------------------------------------------------------- 
1326  integer :: i_val
1327 
1328  i_val = Agrif_nbfixedgrids
1329!---------------------------------------------------------------------------------------------------
1330end function Agrif_Nb_Fine_Grids
1331!===================================================================================================
1332
1333end module Agrif_User_Functions
Note: See TracBrowser for help on using the repository browser.