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

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

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

update AGRIF library

  • Property svn:keywords set to Id
File size: 35.8 KB
Line 
1!
2! $Id$
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!> Module to define some procedures concerning the current grid
24!
25module Agrif_CurgridFunctions
26!
27    use Agrif_Init
28!
29    implicit none
30!
31contains
32!
33!===================================================================================================
34!  function Agrif_rel_dt
35!
36!> Returns the time step of the current grid, relatively to the root grid (for which dt=1.).
37!---------------------------------------------------------------------------------------------------
38function Agrif_rel_dt ( ) result( rel_dt )
39!---------------------------------------------------------------------------------------------------
40    integer :: i
41    real    :: rel_dt
42!
43    rel_dt = 1.
44!
45    do i = 1,Agrif_Probdim
46        rel_dt = min(rel_dt, Agrif_Curgrid % Agrif_dt(i))
47    enddo
48!---------------------------------------------------------------------------------------------------
49end function Agrif_rel_dt
50!===================================================================================================
51!
52!===================================================================================================
53!  function Agrif_rel_idt
54!
55!> Returns the time refinement factor of the current grid, relatively to the root grid (for which idt=1).
56!---------------------------------------------------------------------------------------------------
57function Agrif_rel_idt ( ) result( rel_idt )
58!---------------------------------------------------------------------------------------------------
59    integer :: rel_idt
60!
61    rel_idt = nint(1./Agrif_rel_dt())
62!---------------------------------------------------------------------------------------------------
63end function Agrif_rel_idt
64!===================================================================================================
65!
66!===================================================================================================
67!  function Agrif_IRhot
68!
69!> Returns the time refinement factor of the current grid.
70!---------------------------------------------------------------------------------------------------
71function Agrif_IRhot ( ) result( irhot )
72!---------------------------------------------------------------------------------------------------
73    integer :: i, irhot
74!
75    irhot = 1
76!
77    do i = 1,Agrif_Probdim
78        irhot = max(irhot, Agrif_Curgrid % timeref(i))
79    enddo
80!---------------------------------------------------------------------------------------------------
81end function Agrif_IRhot
82!===================================================================================================
83!
84!===================================================================================================
85!  function Agrif_Rhot
86!
87!> Returns the time refinement factor of the current grid.
88!---------------------------------------------------------------------------------------------------
89function Agrif_Rhot ( ) result( rhot )
90!---------------------------------------------------------------------------------------------------
91    real    :: rhot
92!
93    rhot = float(Agrif_IRhot())
94   
95!---------------------------------------------------------------------------------------------------
96end function Agrif_Rhot
97!===================================================================================================
98!
99!===================================================================================================
100!  function Agrif_Parent_IRhot
101!
102!> Returns the time refinement factor of the parent of the current grid.
103!---------------------------------------------------------------------------------------------------
104function Agrif_Parent_IRhot ( ) result( irhot )
105!---------------------------------------------------------------------------------------------------
106    integer :: i, irhot
107!
108    irhot = 1
109!
110    do i = 1,Agrif_Probdim
111        irhot = max(irhot, Agrif_Curgrid % parent % timeref(i))
112    enddo
113!---------------------------------------------------------------------------------------------------
114end function Agrif_Parent_IRhot
115!===================================================================================================
116!
117!===================================================================================================
118!  function Agrif_Parent_Rhot
119!
120!> Returns the time refinement factor of the parent of the current grid.
121!---------------------------------------------------------------------------------------------------
122function Agrif_Parent_Rhot ( ) result( rhot )
123!---------------------------------------------------------------------------------------------------
124    real :: rhot
125!
126    rhot = float(Agrif_Parent_IRhot())
127!---------------------------------------------------------------------------------------------------
128end function Agrif_Parent_Rhot
129!===================================================================================================
130!
131!===================================================================================================
132!  function Agrif_Nbstepint
133!
134!> function for the calculation of the coefficients used for the time interpolation
135!! (module #Agrif_Boundary).
136!---------------------------------------------------------------------------------------------------
137function Agrif_Nbstepint ( )
138!---------------------------------------------------------------------------------------------------
139    integer :: Agrif_nbstepint ! result
140!
141    Agrif_nbstepint = mod(Agrif_Curgrid % ngridstep, Agrif_iRhot())
142!---------------------------------------------------------------------------------------------------
143end function Agrif_Nbstepint
144!===================================================================================================
145!
146!===================================================================================================
147!  function Agrif_Parent_Nbstepint
148!
149!> function for the calculation of the coefficients used for the time interpolation
150!! (module #Agrif_Boundary).
151!---------------------------------------------------------------------------------------------------
152function Agrif_Parent_Nbstepint ( )
153!---------------------------------------------------------------------------------------------------
154    integer :: Agrif_Parent_Nbstepint ! result
155!
156    Agrif_Parent_Nbstepint = mod(Agrif_Curgrid % parent % ngridstep, int(Agrif_Parent_Rhot()))
157!---------------------------------------------------------------------------------------------------
158end function Agrif_Parent_Nbstepint
159!===================================================================================================
160!
161!===================================================================================================
162!  subroutine Agrif_InterpNearBorderX
163!
164!> Allows to interpolate (in the x direction) on a near border of the current grid if this one
165!! has a common border with the root coarse grid.
166!---------------------------------------------------------------------------------------------------
167subroutine Agrif_InterpNearBorderX ( )
168!---------------------------------------------------------------------------------------------------
169    Agrif_Curgrid % NearRootBorder(1) = .FALSE.
170!---------------------------------------------------------------------------------------------------
171end subroutine Agrif_InterpNearBorderX
172!===================================================================================================
173!
174!===================================================================================================
175!  subroutine Agrif_InterpDistantBorderX
176!
177!> Allows to interpolate (in the x direction) on a distant border of the current grid if this one
178!! has a common border with the root coarse grid.
179!---------------------------------------------------------------------------------------------------
180subroutine Agrif_InterpDistantBorderX ( )
181!---------------------------------------------------------------------------------------------------
182    Agrif_Curgrid % DistantRootBorder(1) = .FALSE.
183!---------------------------------------------------------------------------------------------------
184end subroutine Agrif_InterpDistantBorderX
185!===================================================================================================
186!
187!===================================================================================================
188!  subroutine Agrif_InterpNearBorderY
189!
190!> Allows to interpolate (in the y direction) on a near border of the current grid if this one
191!! has a common border with the root coarse grid.
192!---------------------------------------------------------------------------------------------------
193subroutine Agrif_InterpNearBorderY ( )
194!---------------------------------------------------------------------------------------------------
195    Agrif_Curgrid % NearRootBorder(2) = .FALSE.
196!---------------------------------------------------------------------------------------------------
197end subroutine Agrif_InterpNearBorderY
198!===================================================================================================
199!
200!===================================================================================================
201!  subroutine Agrif_InterpDistantBorderY
202!
203!> Allows to interpolate (in the y direction) on a distant border of the current grid if this one
204!! has a common border with the root coarse grid.
205!---------------------------------------------------------------------------------------------------
206subroutine Agrif_InterpDistantBorderY ( )
207!---------------------------------------------------------------------------------------------------
208    Agrif_Curgrid % DistantRootBorder(2) = .FALSE.
209!---------------------------------------------------------------------------------------------------
210end subroutine Agrif_InterpDistantBorderY
211!===================================================================================================
212!
213!===================================================================================================
214!  subroutine Agrif_InterpNearBorderZ
215!
216!> Allows to interpolate (in the z direction) on a near border of the current grid if this one
217!! has a common border with the root coarse grid.
218!---------------------------------------------------------------------------------------------------
219subroutine Agrif_InterpNearBorderZ ( )
220!---------------------------------------------------------------------------------------------------
221    Agrif_Curgrid % NearRootBorder(3) = .FALSE.
222!---------------------------------------------------------------------------------------------------
223end subroutine Agrif_InterpNearBorderZ
224!===================================================================================================
225!
226!===================================================================================================
227!  subroutine Agrif_InterpDistantBorderZ
228!
229!> Allows to interpolate (in the z direction) on a distant border of the current grid if this one
230!! has a common border with the root coarse grid.
231!---------------------------------------------------------------------------------------------------
232subroutine Agrif_InterpDistantBorderZ()
233!---------------------------------------------------------------------------------------------------
234    Agrif_Curgrid % DistantRootBorder(3) = .FALSE.
235!---------------------------------------------------------------------------------------------------
236end subroutine Agrif_InterpDistantBorderZ
237!===================================================================================================
238!
239!===================================================================================================
240!  function Agrif_Parent_Nb_Step
241!
242!> Returns the number of time steps of the parent of the current grid.
243!---------------------------------------------------------------------------------------------------
244function Agrif_Parent_Nb_Step ( )
245!---------------------------------------------------------------------------------------------------
246    integer :: Agrif_Parent_Nb_Step ! Result
247!
248    if (Agrif_Root()) then
249        Agrif_Parent_Nb_Step = -1
250    else
251        Agrif_Parent_Nb_Step = Agrif_Curgrid % parent % ngridstep
252    endif
253!---------------------------------------------------------------------------------------------------
254end function Agrif_Parent_Nb_Step
255!===================================================================================================
256!
257!===================================================================================================
258!  function Agrif_Root
259!
260!> Indicates if the current grid is or not the root grid.
261!---------------------------------------------------------------------------------------------------
262function Agrif_Root ( )
263!---------------------------------------------------------------------------------------------------
264    logical :: Agrif_Root ! Result
265!
266    Agrif_Root = (Agrif_Curgrid % fixedrank == 0)
267!---------------------------------------------------------------------------------------------------
268end function Agrif_Root
269!===================================================================================================
270!
271!===================================================================================================
272!  function Agrif_GrandMother
273!
274!> Indicates if the current grid is or not the root grid.
275!---------------------------------------------------------------------------------------------------
276function Agrif_GrandMother ( )
277!---------------------------------------------------------------------------------------------------
278    logical :: Agrif_GrandMother ! Result
279!
280    Agrif_GrandMother = Agrif_Curgrid % grand_mother_grid
281!---------------------------------------------------------------------------------------------------
282end function Agrif_GrandMother
283!===================================================================================================
284!
285!===================================================================================================
286!  function Agrif_Parent_Root
287!
288!> Indicates if the parent of the current grid is or not the root grid.
289!---------------------------------------------------------------------------------------------------
290function Agrif_Parent_Root ( )
291!---------------------------------------------------------------------------------------------------
292    logical :: Agrif_Parent_Root ! Result
293!
294    Agrif_Parent_Root = (Agrif_Curgrid % parent % fixedrank == 0)
295!---------------------------------------------------------------------------------------------------
296end function Agrif_Parent_Root
297!===================================================================================================
298!
299!===================================================================================================
300!  function Agrif_Fixed
301!
302!> Returns the number of the current grid.
303!---------------------------------------------------------------------------------------------------
304function Agrif_Fixed ( )
305!---------------------------------------------------------------------------------------------------
306    integer :: Agrif_Fixed   ! Result
307!
308    if (Agrif_Curgrid % fixed) then
309        Agrif_Fixed = Agrif_Curgrid % fixedrank
310    else
311        Agrif_Fixed = -1
312    endif
313!---------------------------------------------------------------------------------------------------
314end function Agrif_Fixed
315!===================================================================================================
316!
317!===================================================================================================
318!  function Agrif_Parent_Fixed
319!
320!> Returns the number of the parent of the current grid.
321!---------------------------------------------------------------------------------------------------
322function Agrif_Parent_Fixed ( )
323!---------------------------------------------------------------------------------------------------
324    integer :: Agrif_Parent_Fixed   ! Result
325!
326    if (Agrif_Curgrid % parent % fixed) then
327        Agrif_Parent_Fixed = Agrif_Curgrid % parent % fixedrank
328    else
329        Agrif_Parent_Fixed = 0
330    endif
331!---------------------------------------------------------------------------------------------------
332end function Agrif_Parent_Fixed
333!===================================================================================================
334!
335!===================================================================================================
336!  function Agrif_Is_Fixed
337!
338!> Returns .TRUE. if the current grid is fixed.
339!---------------------------------------------------------------------------------------------------
340function Agrif_Is_Fixed ( )
341!---------------------------------------------------------------------------------------------------
342    logical :: Agrif_Is_Fixed   ! Result
343!
344    Agrif_Is_Fixed = Agrif_Curgrid % fixed
345!---------------------------------------------------------------------------------------------------
346end function Agrif_Is_Fixed
347!===================================================================================================
348!
349!===================================================================================================
350!  function Agrif_Parent_Is_Fixed
351!
352!> Returns .TRUE. if the parent of the current grid is fixed.
353!---------------------------------------------------------------------------------------------------
354function Agrif_Parent_Is_Fixed ( )
355!---------------------------------------------------------------------------------------------------
356    logical :: Agrif_Parent_Is_Fixed   ! Result
357!
358    Agrif_Parent_Is_Fixed = Agrif_Curgrid % parent % fixed
359!---------------------------------------------------------------------------------------------------
360end function Agrif_Parent_Is_Fixed
361!===================================================================================================
362!
363!===================================================================================================
364!  function Agrif_CFixed
365!
366!> Returns the number of the current grid.
367!---------------------------------------------------------------------------------------------------
368function Agrif_CFixed ( )
369!---------------------------------------------------------------------------------------------------
370    character(3) :: Agrif_CFixed   ! Result
371!
372    character(3) :: cfixed
373    integer      :: fixed
374!
375    fixed = Agrif_Fixed()
376!
377    if (fixed /= -1) then
378!
379        if (fixed <= 9) then
380            write(cfixed,'(i1)') fixed
381        else
382            write(cfixed,'(i2)') fixed
383        endif
384!
385        Agrif_CFixed = cfixed
386       
387        if (associated(agrif_curgrid,agrif_coarsegrid)) then
388          Agrif_CFixed = 'gm'
389        endif
390!
391    else
392        print*,'Call to Agrif_CFixed() on a moving grid'
393        stop
394    endif
395!---------------------------------------------------------------------------------------------------
396end function Agrif_CFixed
397!===================================================================================================
398!
399!===================================================================================================
400!  function Agrid_Parent_CFixed
401!
402!> Returns the number of the parent of the current grid.
403!---------------------------------------------------------------------------------------------------
404function Agrid_Parent_CFixed ( )
405!---------------------------------------------------------------------------------------------------
406    character(3) :: Agrid_Parent_CFixed   ! Result
407!
408    character(3) :: cfixed
409    integer      :: fixed
410!
411    fixed = Agrif_Parent_Fixed()
412!
413    if(fixed /= -1) then
414!
415        if (fixed <= 9) then
416            write(cfixed,'(i1)')fixed
417        else
418            write(cfixed,'(i2)')fixed
419        endif
420!
421        Agrid_Parent_CFixed=cfixed
422!
423    else
424        print*,'Illegal call to Agrid_Parent_CFixed()'
425        stop
426    endif
427!---------------------------------------------------------------------------------------------------
428end function Agrid_Parent_CFixed
429!===================================================================================================
430!
431!===================================================================================================
432!  subroutine Agrif_ChildGrid_to_ParentGrid
433!
434!> Make the pointer #Agrif_Curgrid point on the parent grid of the current grid.
435!---------------------------------------------------------------------------------------------------
436subroutine Agrif_ChildGrid_to_ParentGrid ( )
437!---------------------------------------------------------------------------------------------------
438    Agrif_Curgrid % parent % save_grid => Agrif_Curgrid
439    call Agrif_Instance(Agrif_Curgrid%parent)
440!---------------------------------------------------------------------------------------------------
441end subroutine Agrif_ChildGrid_to_ParentGrid
442!===================================================================================================
443!
444!===================================================================================================
445!  subroutine Agrif_ParentGrid_to_ChildGrid
446!
447!> Make the pointer #Agrif_Curgrid point on the child grid after having called the
448!! #Agrif_ChildGrid_to_ParentGrid subroutine.
449!---------------------------------------------------------------------------------------------------
450subroutine Agrif_ParentGrid_to_ChildGrid ( )
451!---------------------------------------------------------------------------------------------------
452    call Agrif_Instance(Agrif_Curgrid%save_grid)
453!---------------------------------------------------------------------------------------------------
454end subroutine Agrif_ParentGrid_to_ChildGrid
455!===================================================================================================
456!
457!===================================================================================================
458!  function Agrif_Get_Unit
459!
460!> Returns a unit not connected to any file.
461!---------------------------------------------------------------------------------------------------
462function Agrif_Get_Unit ( )
463!---------------------------------------------------------------------------------------------------
464    integer :: Agrif_Get_Unit  ! Result
465!
466    integer :: n
467    logical :: op
468!
469    integer :: nunit
470    integer :: iii, out, iiimax
471    logical :: bexist
472    integer,dimension(1:1000) :: forbiddenunit
473!
474!   Load forbidden Unit if the file Agrif_forbidenUnit exist
475!
476    INQUIRE(file='Agrif_forbiddenUnit.txt', exist=bexist)
477!
478    if (.not. bexist) then
479!       File Agrif_forbiddenUnit.txt not found
480    else
481        nunit = 777
482        OPEN(nunit,file='Agrif_forbiddenUnit.txt', form='formatted', status="old")
483        iii = 1
484        do while ( .TRUE. )
485            READ(nunit,*, end=99) forbiddenunit(iii)
486            iii = iii + 1
487        enddo
488   99   continue
489        iiimax = iii
490        close(nunit)
491    endif
492!
493    do n = 7,1000
494!
495        INQUIRE(Unit=n,Opened=op)
496!
497        out = 0
498        if ( bexist .AND. (.NOT.op) ) then
499            do iii = 1,iiimax
500                if ( n == forbiddenunit(iii) ) out = 1
501            enddo
502        endif
503!
504        if ( (.NOT.op) .AND. (out == 0) ) exit
505!
506    enddo
507!
508    Agrif_Get_Unit = n
509!---------------------------------------------------------------------------------------------------
510end function Agrif_Get_Unit
511!===================================================================================================
512!
513!===================================================================================================
514!  subroutine Agrif_Set_Extra_Boundary_Cells
515!---------------------------------------------------------------------------------------------------
516subroutine Agrif_Set_Extra_Boundary_Cells ( nb_extra_cells )
517!---------------------------------------------------------------------------------------------------
518    integer, intent(in) :: nb_extra_cells
519!
520    Agrif_Extra_Boundary_Cells = nb_extra_cells
521!---------------------------------------------------------------------------------------------------
522end subroutine Agrif_Set_Extra_Boundary_Cells
523!===================================================================================================
524!
525!===================================================================================================
526!  subroutine Agrif_Set_Efficiency
527!---------------------------------------------------------------------------------------------------
528subroutine Agrif_Set_Efficiency ( eff )
529!---------------------------------------------------------------------------------------------------
530    real, intent(in) :: eff
531!
532    if ( (eff < 0.) .OR. (eff > 1) ) then
533        write(*,*) 'Error Efficiency should be between 0 and 1'
534        stop
535    else
536        Agrif_Efficiency = eff
537    endif
538!---------------------------------------------------------------------------------------------------
539end subroutine Agrif_Set_Efficiency
540!===================================================================================================
541!
542!===================================================================================================
543!  subroutine Agrif_Set_Regridding
544!---------------------------------------------------------------------------------------------------
545subroutine Agrif_Set_Regridding ( regfreq )
546!---------------------------------------------------------------------------------------------------
547    integer, intent(in) :: regfreq
548!
549    if (regfreq < 0) then
550        write(*,*) 'Regridding frequency should be positive'
551        stop
552    else
553        Agrif_Regridding = regfreq
554    endif
555!---------------------------------------------------------------------------------------------------
556end subroutine Agrif_Set_Regridding
557!===================================================================================================
558!
559!===================================================================================================
560!  subroutine Agrif_Set_coeffref_x
561!---------------------------------------------------------------------------------------------------
562subroutine Agrif_Set_coeffref_x ( coeffref )
563!---------------------------------------------------------------------------------------------------
564    integer, intent(in) :: coeffref
565
566      if (coeffref < 0) then
567         write(*,*) 'Coefficient of raffinement should be positive'
568         stop
569      else
570         Agrif_coeffref(1) = coeffref
571      endif
572!---------------------------------------------------------------------------------------------------
573end subroutine Agrif_Set_coeffref_x
574!===================================================================================================
575!
576!===================================================================================================
577!  subroutine Agrif_Set_coeffref_y
578!---------------------------------------------------------------------------------------------------
579subroutine Agrif_Set_coeffref_y ( coeffref )
580!---------------------------------------------------------------------------------------------------
581    integer, intent(in) :: coeffref
582
583    if (coeffref < 0) then
584        write(*,*) 'Coefficient of raffinement should be positive'
585        stop
586    else
587        Agrif_coeffref(2) = coeffref
588    endif
589!---------------------------------------------------------------------------------------------------
590end subroutine Agrif_Set_coeffref_y
591!===================================================================================================
592!
593!===================================================================================================
594!  subroutine Agrif_Set_coeffref_z
595!---------------------------------------------------------------------------------------------------
596subroutine Agrif_Set_coeffref_z ( coeffref )
597!---------------------------------------------------------------------------------------------------
598    integer, intent(in) :: coeffref
599!
600    if (coeffref < 0) then
601        write(*,*) 'Coefficient of raffinement should be positive'
602        stop
603    else
604        Agrif_coeffref(3) = coeffref
605    endif
606!---------------------------------------------------------------------------------------------------
607end subroutine Agrif_Set_coeffref_z
608!===================================================================================================
609!
610!===================================================================================================
611!  subroutine Agrif_Set_coeffreft_x
612!---------------------------------------------------------------------------------------------------
613subroutine Agrif_Set_coeffreft_x ( coeffref )
614!---------------------------------------------------------------------------------------------------
615    integer, intent(in) :: coeffref
616
617    if (coeffref < 0) then
618        write(*,*) 'Coefficient of time raffinement should be positive'
619        stop
620    else
621        Agrif_coeffreft(1) = coeffref
622    endif
623!---------------------------------------------------------------------------------------------------
624end subroutine Agrif_Set_coeffreft_x
625!===================================================================================================
626!
627!===================================================================================================
628!  subroutine Agrif_Set_coeffreft_y
629!---------------------------------------------------------------------------------------------------
630subroutine Agrif_Set_coeffreft_y ( coeffref )
631!---------------------------------------------------------------------------------------------------
632    integer, intent(in) :: coeffref
633!
634    if (coeffref < 0) then
635        write(*,*) 'Coefficient of time raffinement should be positive'
636        stop
637    else
638        Agrif_coeffreft(2) = coeffref
639    endif
640!---------------------------------------------------------------------------------------------------
641end subroutine Agrif_Set_coeffreft_y
642!===================================================================================================
643!
644!===================================================================================================
645!  subroutine Agrif_Set_coeffreft_z
646!---------------------------------------------------------------------------------------------------
647subroutine Agrif_Set_coeffreft_z ( coeffref )
648!---------------------------------------------------------------------------------------------------
649    integer, intent(in) :: coeffref
650
651    if (coeffref < 0) then
652        write(*,*)'Coefficient of time raffinement should be positive'
653        stop
654    else
655        Agrif_coeffreft(3) = coeffref
656    endif
657!---------------------------------------------------------------------------------------------------
658end subroutine Agrif_Set_coeffreft_z
659!===================================================================================================
660!
661!===================================================================================================
662!  subroutine Agrif_Set_Minwidth
663!---------------------------------------------------------------------------------------------------
664subroutine Agrif_Set_Minwidth ( coefminwidth )
665!---------------------------------------------------------------------------------------------------
666    integer, intent(in) :: coefminwidth
667!
668    if (coefminwidth < 0) then
669        write(*,*)'Coefficient of Minwidth should be positive'
670        stop
671    else
672        Agrif_Minwidth = coefminwidth
673    endif
674!---------------------------------------------------------------------------------------------------
675end subroutine Agrif_Set_Minwidth
676!===================================================================================================
677!
678!===================================================================================================
679!  subroutine Agrif_Set_Rafmax
680!---------------------------------------------------------------------------------------------------
681subroutine Agrif_Set_Rafmax ( coefrafmax )
682!---------------------------------------------------------------------------------------------------
683    integer, intent(in) :: coefrafmax
684!
685    integer :: i
686    real    :: res
687!
688    if (coefrafmax < 0) then
689        write(*,*)'Coefficient of  should be positive'
690        stop
691    else
692        res = 1.
693        do i = 1,coefrafmax-1
694            res = res * FLOAT(Agrif_coeffref(1))
695        enddo
696        if ( res == 0 ) res = 1
697        Agrif_Mind(1) = 1. / res
698!
699        res = 1.
700        do i = 1,coefrafmax-1
701            res = res * FLOAT(Agrif_coeffref(2))
702        enddo
703        if ( res == 0 ) res = 1
704        Agrif_Mind(2) = 1. / res
705!
706        res = 1.
707        do i = 1,coefrafmax-1
708            res = res * FLOAT(Agrif_coeffref(3))
709        enddo
710        if ( res == 0 ) res = 1
711        Agrif_Mind(3) = 1. / res
712!
713      endif
714!---------------------------------------------------------------------------------------------------
715end subroutine Agrif_Set_Rafmax
716!===================================================================================================
717!
718!===================================================================================================
719!  subroutine Agrif_Set_MaskMaxSearch
720!---------------------------------------------------------------------------------------------------
721subroutine Agrif_Set_MaskMaxSearch ( mymaxsearch )
722!---------------------------------------------------------------------------------------------------
723    integer, intent(in) :: mymaxsearch
724!
725    MaxSearch = mymaxsearch
726!---------------------------------------------------------------------------------------------------
727end subroutine Agrif_Set_MaskMaxSearch
728!===================================================================================================
729!
730!===================================================================================================
731!  function Agrif_Level
732!---------------------------------------------------------------------------------------------------
733function Agrif_Level ( )
734!---------------------------------------------------------------------------------------------------
735    integer :: Agrif_Level  ! Result
736!
737    Agrif_Level = Agrif_Curgrid % level
738!---------------------------------------------------------------------------------------------------
739end function Agrif_Level
740!===================================================================================================
741!
742!===================================================================================================
743!  function Agrif_MaxLevel
744!---------------------------------------------------------------------------------------------------
745function Agrif_MaxLevel ( )
746!---------------------------------------------------------------------------------------------------
747    integer :: Agrif_MaxLevel  ! Result
748!
749    Agrif_MaxLevel = Agrif_MaxLevelLoc
750!---------------------------------------------------------------------------------------------------
751end function Agrif_MaxLevel
752!===================================================================================================
753!
754!===================================================================================================
755!  function Agrif_GridAllocation_is_done
756!---------------------------------------------------------------------------------------------------
757function Agrif_GridAllocation_is_done ( ) result(isdone)
758!---------------------------------------------------------------------------------------------------
759    logical :: isdone
760!
761    isdone = Agrif_Curgrid % allocation_is_done
762!---------------------------------------------------------------------------------------------------
763end function Agrif_GridAllocation_is_done
764!===================================================================================================
765!
766end module Agrif_CurgridFunctions
Note: See TracBrowser for help on using the repository browser.