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.
modutil.F in trunk/AGRIF/AGRIF_FILES – NEMO

source: trunk/AGRIF/AGRIF_FILES/modutil.F @ 396

Last change on this file since 396 was 396, checked in by opalod, 18 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 23.9 KB
Line 
1!
2! $Id$
3!
4C     Agrif (Adaptive Grid Refinement In Fortran)
5C
6C     Copyright (C) 2003 Laurent Debreu (Laurent.Debreu@imag.fr)
7C                        Christophe Vouland (Christophe.Vouland@imag.fr)   
8C
9C     This program is free software; you can redistribute it and/or modify
10C     it under the terms of the GNU General Public License as published by
11C     the Free Software Foundation; either version 2 of the License, or
12C     (at your option) any later version.
13C
14C     This program is distributed in the hope that it will be useful,
15C     but WITHOUT ANY WARRANTY; without even the implied warranty of
16C     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
17C     GNU General Public License for more details.
18C
19C     You should have received a copy of the GNU General Public License
20C     along with this program; if not, write to the Free Software
21C     Foundation, Inc., 59 Temple Place-  Suite 330, Boston, MA 02111-1307, USA.
22C
23C
24C
25CCC   Module Agrif_Util 
26C 
27      Module Agrif_Util 
28C
29C
30CCC   Description:   
31CCC   This module contains the two procedures called in the main program : 
32CCC   Agrif_Init_Grids allowing the initialization of the root coarse grid, and
33CCC   Agrif_Step allowing the creation of the grid hierarchy and the management
34CCC   of the time integration. 
35C
36C     Modules used:
37C
38      Use Agrif_Clustering   
39      Use Agrif_bcfunction
40C     
41      IMPLICIT NONE
42C
43      Contains
44C     Definition of procedures contained in this module.
45C
46C     **************************************************************************
47CCC   Subroutine Agrif_Step
48C     **************************************************************************
49C 
50      Subroutine Agrif_Step(procname) 
51C
52CCC   Description:
53CCC   Subroutine to create the grid hierarchy and to manage the time integration 
54CCC   procedure. It is called in the main program.
55C
56CC    Method:
57CC    Call on subroutines Agrif_Regrid and Agrif_Integrate.
58C
59C     Declarations:
60C
61      Optional :: procname
62      External :: procname
63C
64#ifdef AGRIF_MPI
65      Integer      :: code
66#include "mpif.h"
67C
68C
69      If (Agrif_Mygrid % ngridstep == 0) Then
70          Call MPI_COMM_SIZE(MPI_COMM_WORLD,Agrif_Nbprocs,code)
71          Call MPI_COMM_RANK(MPI_COMM_WORLD,Agrif_ProcRank,code)
72          Call MPI_COMM_GROUP(MPI_COMM_WORLD,Agrif_Group,code)
73      endif
74#endif
75C
76C     Creation and initialization of the grid hierarchy 
77C
78C 
79C    Set the clustering variables
80C
81      Call Agrif_clustering_def()
82C     
83      if ( Agrif_USE_ONLY_FIXED_GRIDS .EQ. 1 ) then
84C     
85         If (Agrif_Mygrid % ngridstep == 0) then
86C
87            Call Agrif_Regrid
88C 
89            Call Agrif_Instance           
90     &          (Agrif_Mygrid)           
91         endif
92C
93      else
94C   
95         If (mod(Agrif_Mygrid % ngridstep, Agrif_Regridding) == 0) then
96C
97            Call Agrif_Regrid
98C 
99            Call Agrif_Instance           
100     &          (Agrif_Mygrid) 
101C           
102         endif
103C
104      endif
105C
106C     Time integration of the grid hierarchy
107C
108      If (present(procname)) Then
109         Call Agrif_Integrate (Agrif_Mygrid,procname)
110      Else
111         Call Agrif_Integrate (Agrif_Mygrid)     
112      endif
113C   
114      If (associated(Agrif_Mygrid%child_grids)) 
115     &   Call Agrif_Instance (Agrif_Mygrid)
116C
117      Return
118C             
119      End Subroutine Agrif_Step     
120
121C     **************************************************************************
122CCC   Subroutine Agrif_Step_Child
123C     **************************************************************************
124C
125      Subroutine Agrif_Step_Child(procname)
126C
127CCC   Description:
128CCC   Subroutine to create the grid hierarchy and to manage the time integration
129CCC   procedure. It is called in the main program.
130C
131CC    Method:
132CC    Call on subroutines Agrif_Regrid and Agrif_Integrate.
133C
134C     Declarations:
135C
136      Optional :: procname
137      External :: procname
138C
139C     Time integration of the grid hierarchy
140C
141      If (present(procname)) Then
142         Call Agrif_Integrate_Child (Agrif_Mygrid,procname)
143      Else
144         Call Agrif_Integrate_Child (Agrif_Mygrid)
145      endif
146C   
147      If (associated(Agrif_Mygrid%child_grids))
148     &   Call Agrif_Instance (Agrif_Mygrid)
149C
150      Return
151C
152      End Subroutine Agrif_Step_Child
153
154C
155C
156C
157C     **************************************************************************
158CCC   Subroutine Agrif_Regrid
159C     **************************************************************************
160C
161      Subroutine Agrif_Regrid
162C
163CCC   Description:
164CCC   Subroutine to create the grid hierarchy from fixed grids and
165CC       adaptive mesh refinement.
166C
167CC    Method:       
168C
169C     Declarations:
170C
171C     Local variables     
172      Type(Agrif_Rectangle), Pointer     :: coarsegrid_fixed
173      Type(Agrif_Rectangle), Pointer     :: coarsegrid_moving 
174      INTEGER                            :: j
175      INTEGER :: nunit
176      INTEGER                            :: iii
177      Logical :: BEXIST
178C 
179      if ( Agrif_USE_ONLY_FIXED_GRIDS .EQ. 0 )
180     &   Call Agrif_detect_all(Agrif_Mygrid) ! Detection of areas to be refined
181C
182      Allocate(coarsegrid_fixed)
183      Allocate(coarsegrid_moving)
184C
185      if ( Agrif_USE_ONLY_FIXED_GRIDS .EQ. 0 ) 
186     &    Call Agrif_Cluster_All(Agrif_Mygrid,coarsegrid_moving) ! Clustering
187C
188      if ( Agrif_USE_FIXED_GRIDS .EQ. 1 .OR. 
189     &     Agrif_USE_ONLY_FIXED_GRIDS .EQ. 1 ) then
190C
191      If (Agrif_Mygrid % ngridstep == 0) Then
192          nunit = Agrif_Get_Unit()
193          open(nunit,file='AGRIF_FixedGrids.in',form='formatted',
194     &           status="old",ERR=99) ! Opening of the Agrif_FixedGrids.in file
195          j = 1
196C         Creation of the grid hierarchy from the Agrif_FixedGrids.in file 
197            do iii = 1 , Agrif_Probdim
198               coarsegrid_fixed % imin(iii) = 1
199               coarsegrid_fixed % imax(iii) = Agrif_Mygrid % nb(iii) + 1
200            enddo
201C     
202            Call Agrif_Read_Fix_Grd (coarsegrid_fixed,j,nunit)     
203            close(nunit) ! Closing of the Agrif_FixedGrids.in file
204C
205          Nullify(Agrif_oldmygrid)
206          Nullify(Agrif_Mygrid  % child_grids)
207C       
208C         Creation of the grid hierarchy from coarsegrid_fixed
209            Call Agrif_Create_Grids (Agrif_Mygrid,coarsegrid_fixed)
210        Else       
211          Agrif_oldmygrid => Agrif_Mygrid % child_grids
212         endif
213      else
214      Agrif_oldmygrid => Agrif_Mygrid % child_grids
215      Nullify(Agrif_Mygrid  % child_grids)
216      endif
217C
218      if ( Agrif_USE_ONLY_FIXED_GRIDS .EQ. 0 ) then
219C     
220      Call Agrif_Free_before_All(Agrif_oldmygrid)
221C 
222C     Creation of the grid hierarchy from coarsegrid_moving   
223      Call Agrif_Create_Grids
224     &     (Agrif_Mygrid,coarsegrid_moving)
225C
226      endif
227C
228C     Initialization of the grid hierarchy by copy or interpolation
229C
230      Call Agrif_Init_Hierarchy(Agrif_Mygrid)
231C
232      if ( Agrif_USE_ONLY_FIXED_GRIDS .EQ. 0 ) 
233     &        Call Agrif_Free_after_All(Agrif_oldmygrid)
234C
235      Deallocate(coarsegrid_fixed)
236      Deallocate(coarsegrid_moving)
237C     
238      Return
239C
240C     Opening error
241C
242   99 INQUIRE(FILE='AGRIF_FixedGrids.in',EXIST=BEXIST)
243      If (.not. BEXIST) Then
244          print*,'ERROR : File AGRIF_FixedGrids.in not found.'
245          STOP
246        Else
247          print*,'Error opening file AGRIF_FixedGrids.in'
248          STOP         
249      endif     
250C     
251      End Subroutine Agrif_Regrid
252C
253C     **************************************************************************
254CCC   Subroutine Agrif_detect_All
255C     **************************************************************************
256C
257      Recursive Subroutine Agrif_detect_all(g)
258C
259CCC   Description:
260CCC   Subroutine to detect areas to be refined.
261C
262CC    Method:       
263C
264C     Declarations:
265C
266     
267C     
268C     Pointer argument   
269      TYPE(Agrif_Grid) ,pointer  :: g        ! Pointer on the current grid
270C     
271C     Local variables
272      Type(Agrif_pgrid),pointer  :: parcours ! Pointer for the recursive
273                                             ! procedure     
274      INTEGER, DIMENSION(3)      :: size
275      INTEGER                    :: iii
276      Real :: g_eps     
277C
278      parcours => g % child_grids
279C 
280C     To be positioned on the finer grids of the grid hierarchy         
281C 
282      do while (associated(parcours))       
283         Call Agrif_detect_all (parcours % gr) 
284        parcours => parcours % next             
285      enddo
286C
287      g_eps = huge(1.)
288      do iii = 1 , Agrif_Probdim
289         g_eps=min(g_eps,g%Agrif_d(iii))
290      enddo
291C
292      g_eps = g_eps/100.
293C         
294      if ( Agrif_Probdim .EQ. 1 ) g%tabpoint1D=0
295      if ( Agrif_Probdim .EQ. 2 ) g%tabpoint2D=0
296      if ( Agrif_Probdim .EQ. 3 ) g%tabpoint3D=0
297C     
298      do iii = 1 , Agrif_Probdim
299         if (g%Agrif_d(iii)/Agrif_coeffref(iii).LT.
300     &                     (Agrif_mind(iii)-g_eps)) Return
301      enddo
302C                                       
303      Call Agrif_instance(g)
304C 
305C     Detection (Agrif_detect is a user s routine)
306C     
307      do iii = 1 , Agrif_Probdim
308         size(iii) = g%nb(iii) + 1
309      enddo
310C
311      SELECT CASE (Agrif_Probdim)
312      CASE (1) 
313         Call Agrif_detect(g%tabpoint1D,size)
314      CASE (2) 
315         Call Agrif_detect(g%tabpoint2D,size)
316      CASE (3) 
317         Call Agrif_detect(g%tabpoint3D,size)
318      END SELECT
319C
320C     Addition of the areas detected on the child grids
321C     
322      parcours => g % child_grids 
323C           
324      Do while (associated(parcours))
325        Call Agrif_Add_detected_areas (g,parcours % gr)
326        parcours => parcours % next 
327      enddo
328C     
329      Return     
330C
331      End Subroutine Agrif_detect_all
332C     
333C
334C
335C     **************************************************************************
336CCC   Subroutine Agrif_Add_detected_areas
337C     **************************************************************************
338C     
339      Subroutine Agrif_Add_detected_areas(parentgrid,childgrid)
340C
341CCC   Description:
342CCC   Subroutine to add on the parent grid the areas detected 
343CC       on its child grids.
344C
345CC    Method:       
346C
347C     Declarations:
348C
349     
350C 
351      Type(Agrif_Grid),pointer   :: parentgrid,childgrid
352C     
353      Integer :: i,j,k
354C
355      do i = 1,childgrid%nb(1)+1
356         if ( Agrif_Probdim .EQ. 1 ) then
357            If (childgrid%tabpoint1D(i).EQ.1) Then
358                parentgrid%tabpoint1D(childgrid%ix(1)+
359     &                 (i-1)/Agrif_Coeffref(1)) = 1
360            endif
361         else
362            do j=1,childgrid%nb(2)+1
363               if (Agrif_Probdim.EQ.2) then
364              If (childgrid%tabpoint2D(i,j).EQ.1) Then
365                  parentgrid%tabpoint2D(
366     &                  childgrid%ix(1)+(i-1)/Agrif_Coeffref(1),
367     &                  childgrid%ix(2)+(j-1)/Agrif_Coeffref(2)) = 1
368                  endif
369               else
370                  do k=1,childgrid%nb(3)+1
371                If (childgrid%tabpoint3D(i,j,k).EQ.1) Then
372                    parentgrid%tabpoint3D(
373     &                     childgrid%ix(1)+(i-1)/Agrif_Coeffref(1),
374     &                     childgrid%ix(2)+(j-1)/Agrif_Coeffref(2),
375     &                     childgrid%ix(3)+(k-1)/Agrif_Coeffref(3)) = 1
376                     endif
377                  enddo
378               endif
379            enddo
380         endif
381      enddo
382C     
383      Return
384C
385      End Subroutine Agrif_Add_detected_areas   
386C     
387C
388C     **************************************************************************
389CCC   Subroutine Agrif_Free_before_All
390C     **************************************************************************
391C
392      Recursive Subroutine Agrif_Free_before_All(g)
393C
394CCC   Description:
395C
396CC    Method:       
397C
398C     Declarations:
399C
400C     Pointer argument   
401      Type(Agrif_pgrid),pointer   :: g        ! Pointer on the current grid
402C
403C     Local pointer
404      Type(Agrif_pgrid),pointer  :: parcours ! Pointer for the recursive
405                                             ! procedure     
406C
407C
408      parcours => g       
409C     
410      Do while (associated(parcours))     
411        If (.not. parcours%gr%fixed) Then
412            Call Agrif_Free_data_before(parcours%gr)
413            parcours % gr % oldgrid = .TRUE.       
414        endif
415C
416        Call Agrif_Free_before_all (parcours % gr % child_grids)
417C 
418        parcours => parcours % next             
419      enddo
420C     
421      Return     
422C
423C
424      End Subroutine Agrif_Free_before_All
425C
426C
427C
428C     **************************************************************************
429CCC   Subroutine Agrif_Free_after_All
430C     **************************************************************************
431C
432      Recursive Subroutine Agrif_Free_after_All(g)
433C
434CCC   Description:
435C
436CC    Method:       
437C
438C     Declarations:
439C
440     
441C     
442C     Pointer argument   
443      Type(Agrif_pgrid),pointer   :: g       ! Pointer on the current grid
444C
445C     Local pointers
446      TYPE(Agrif_pgrid),pointer  :: parcours ! Pointer for the recursive proced
447      Type(Agrif_pgrid),pointer  :: preparcours   
448      Type(Agrif_pgrid),pointer  :: preparcoursini 
449C
450C
451      Allocate(preparcours)
452C 
453      preparcoursini => preparcours
454C 
455      Nullify(preparcours % gr)
456C 
457      preparcours % next => g
458C
459      parcours => g
460C     
461      Do while (associated(parcours))
462C
463         if ( (.NOT. parcours% gr% fixed) .AND.
464     &        (parcours% gr% oldgrid    ) ) then
465          Call Agrif_Free_data_after(parcours%gr)
466         endif
467C
468         Call Agrif_Free_after_all (parcours % gr % child_grids)
469C
470      If (parcours % gr % oldgrid) Then
471          Deallocate(parcours % gr)
472          preparcours % next => parcours % next
473          Deallocate(parcours)
474          parcours => preparcours % next
475        Else
476          preparcours => preparcours % next
477          parcours => parcours % next 
478         endif       
479      enddo
480C
481      Deallocate(preparcoursini)
482C     
483      Return     
484C
485      End Subroutine Agrif_Free_after_All
486C
487C
488C     **************************************************************************
489CCC   Subroutine Agrif_Integrate
490C     **************************************************************************
491C
492      Recursive Subroutine Agrif_Integrate(g, procname)         
493C
494CCC   Description:
495CCC   Subroutine to manage the time integration of the grid hierarchy.
496C
497CC    Method:
498CC    Recursive subroutine and call on subroutines Agrif_Instance & Agrif_Step
499C
500C     Declarations:
501C
502     
503C     
504C     Pointer argument   
505      Type(Agrif_Grid),pointer   :: g        ! Pointer on the current grid
506C
507C     main procedure name
508      Optional :: procname
509      External :: procname     
510C     
511C     Local pointer
512      Type(Agrif_pgrid),pointer  :: parcours ! Pointer for the recursive
513                                             ! procedure
514C
515C     Local scalars
516      INTEGER                    :: nbt      ! Number of time steps
517                                             ! of the current grid
518      INTEGER                    :: k       
519      INTEGER                    :: iii
520C 
521C     Instanciation of the variables of the current grid
522      If (g%fixedrank .NE.0) Then     
523      Call Agrif_Instance
524     &     (g)
525      End If
526C       
527C     One step on the current grid     
528C
529      If (present(procname)) Then
530         Call procname ()     
531      Else
532        write(*,*) 'The name of the step subroutine has not '
533        write(*,*) 'been given in the subroutine Agrif_Integrate'
534        stop
535      endif
536C
537C     Number of time steps on the current grid     
538C
539      g%ngridstep = g % ngridstep + 1
540C     
541      parcours => g % child_grids
542C   
543C     Recursive procedure for the time integration of the grid hierarchy     
544      Do while (associated(parcours))
545C
546C       Instanciation of the variables of the current grid           
547        Call Agrif_Instance
548     &           (parcours % gr)
549C       
550C       Number of time steps
551        nbt = 1
552        do iii = 1 , Agrif_Probdim
553           nbt = max(nbt, parcours % gr % timeref(iii))
554        enddo
555C       
556        Do k = 1,nbt
557C       
558           If (present(procname)) Then
559                 Call Agrif_Integrate (parcours % gr, procname)
560           Else
561                 Call Agrif_Integrate (parcours % gr)     
562           endif
563C       
564        enddo     
565C 
566        parcours => parcours % next
567C     
568      enddo
569C
570C     
571      End Subroutine Agrif_Integrate 
572
573C     **************************************************************************
574CCC   Subroutine Agrif_Integrate_Child
575C     **************************************************************************
576C
577      Recursive Subroutine Agrif_Integrate_Child(g,procname)
578C
579CCC   Description:
580CCC   Subroutine to manage the time integration of the grid hierarchy.
581C
582CC    Method:
583CC    Recursive subroutine and call on subroutines Agrif_Instance & Agrif_Step.
584C
585C     Declarations:
586C
587
588C
589C     Pointer argument
590      Type(Agrif_Grid),pointer   :: g        ! Pointer on the current grid
591C
592C     main procedure name
593      Optional :: procname
594      External :: procname
595C
596C     Local pointer
597      Type(Agrif_pgrid),pointer  :: parcours ! Pointer for the recursive
598                                             ! procedure
599C
600C     One step on the current grid
601C
602      If (present(procname)) Then
603         Call procname ()     
604      Else
605        write(*,*) 'The name of the step subroutine has not '
606        write(*,*) 'been given in the subroutine Agrif_Integrate'
607        stop
608      endif
609C
610C     Number of time steps on the current grid
611C
612C
613      parcours => g % child_grids
614C
615C     Recursive procedure for the time integration of the grid hierarchy     
616      Do while (associated(parcours))
617C
618C       Instanciation of the variables of the current grid
619        Call Agrif_Instance
620     &           (parcours % gr)
621
622C       
623           If (present(procname)) Then
624                 Call Agrif_Integrate_Child (parcours % gr, procname)
625           Else
626                 Call Agrif_Integrate_Child (parcours % gr)
627           endif
628C 
629        parcours => parcours % next
630C     
631      enddo
632C
633C
634      End Subroutine Agrif_Integrate_Child
635
636C
637C
638C     **************************************************************************
639CCC   Subroutine Agrif_Init_Grids
640C     **************************************************************************
641C     
642      Subroutine Agrif_Init_Grids
643C
644CCC   Description:
645CCC   Subroutine to initialize the root coarse grid pointed by Agrif_Mygrid. 
646CCC   It is called in the main program.
647C
648C     Declarations:
649C
650C
651      INTEGER :: iii
652C
653C             definition of the probdim and modtypes variables
654C
655#ifdef AGRIF_MPI
656#include "mpif.h"
657      Agrif_MPIPREC = MPI_DOUBLE_PRECISION
658#endif
659      Call Agrif_probdim_modtype_def()
660C     
661      Agrif_UseSpecialValue = .FALSE.
662      Agrif_UseSpecialValueFineGrid = .FALSE.
663      Agrif_SpecialValue = 0.
664      Agrif_SpecialValueFineGrid = 0.
665C     
666C     Allocation of Agrif_Mygrid
667      allocate(Agrif_Mygrid)
668C     
669C     Space and time refinement factors are set to 1 on the root grid
670C
671      do iii = 1 , Agrif_Probdim
672         Agrif_Mygrid % spaceref(iii) = 1
673         Agrif_Mygrid % timeref(iii) = 1
674      enddo
675C     
676C     Initialization of the number of time steps   
677      Agrif_Mygrid % ngridstep = 0
678      Agrif_Mygrid % grid_id = 0
679C
680C     No parent grid for the root coarse grid
681      Nullify(Agrif_Mygrid % parent)
682C     
683C     Initialization of the minimum positions, global abscissa and space steps 
684      do iii= 1 ,  Agrif_Probdim
685         Agrif_Mygrid % ix(iii) = 1           
686         Agrif_Mygrid % Agrif_x(iii) = 0.
687         Agrif_Mygrid % Agrif_d(iii) = 1. 
688C     Borders of the root coarse grid 
689         Agrif_Mygrid % NearRootBorder(iii) = .true. 
690         Agrif_Mygrid % DistantRootBorder(iii) = .true.     
691      enddo
692C 
693C     The root coarse grid is a fixed grid
694      Agrif_Mygrid % fixed = .TRUE.
695C     
696C     Number of the grid pointed by Agrif_Mygrid (root coarse grid)
697      Agrif_Mygrid % rank = 1     
698C 
699C     Number of the root grid as a fixed grid   
700      Agrif_Mygrid % fixedrank = 0 
701C 
702C     Initialization of some fields of the root grid variables     
703      Call Agrif_Create_Var (Agrif_Mygrid)
704C     
705C     Initialization of the other fields of the root grid variables (number of 
706C     cells, positions, number and type of its dimensions, ...) 
707      Call Agrif_Set_numberofcells(Agrif_Mygrid)
708C     
709      Call Agrif_Instance (Agrif_Mygrid)       
710C             
711C     Allocation of the array containing the values of the grid variables
712      Call Agrif_Allocation (Agrif_Mygrid)
713C       
714      Call Agrif_initialisations(Agrif_Mygrid)
715C     
716      nullify(Agrif_Mygrid % child_grids)
717C 
718C     Total number of fixed grids   
719      Agrif_nbfixedgrids = 0         
720C     
721      Call Agrif_Instance (Agrif_Mygrid)
722C       
723      End Subroutine Agrif_Init_Grids 
724C
725C
726C     **************************************************************************
727CCC   Subroutine Agrif_Deallocation
728C     **************************************************************************
729C     
730      Subroutine Agrif_Deallocation
731C
732CCC   Description:
733CCC   Subroutine to initialize the root coarse grid pointed by Agrif_Mygrid. 
734CCC   It is called in the main program.
735C
736C     Declarations:
737C
738C
739      INTEGER :: nb
740C
741C             definition of the probdim and modtypes variables
742C
743      do nb = 1, Agrif_NbVariables
744          if ( associated(Agrif_Mygrid % tabvars(nb) % var % array1) ) 
745     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % array1)
746          if ( associated(Agrif_Mygrid % tabvars(nb) % var % array2) ) 
747     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % array2)
748          if ( associated(Agrif_Mygrid % tabvars(nb) % var % array3) ) 
749     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % array3)
750          if ( associated(Agrif_Mygrid % tabvars(nb) % var % array4) ) 
751     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % array4)
752          if ( associated(Agrif_Mygrid % tabvars(nb) % var % array5) ) 
753     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % array5)
754          if ( associated(Agrif_Mygrid % tabvars(nb) % var % array6) ) 
755     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % array6)
756C
757          if ( associated(Agrif_Mygrid % tabvars(nb) % var % iarray1) ) 
758     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % iarray1)
759          if ( associated(Agrif_Mygrid % tabvars(nb) % var % iarray2) ) 
760     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % iarray2)
761          if ( associated(Agrif_Mygrid % tabvars(nb) % var % iarray3) ) 
762     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % iarray3)
763          if ( associated(Agrif_Mygrid % tabvars(nb) % var % iarray4) ) 
764     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % iarray4)
765          if ( associated(Agrif_Mygrid % tabvars(nb) % var % iarray5) ) 
766     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % iarray5)
767          if ( associated(Agrif_Mygrid % tabvars(nb) % var % iarray6) ) 
768     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % iarray6)
769C
770          if ( associated(Agrif_Mygrid % tabvars(nb) % var % larray1) ) 
771     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % larray1)
772          if ( associated(Agrif_Mygrid % tabvars(nb) % var % larray2) ) 
773     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % larray2)
774          if ( associated(Agrif_Mygrid % tabvars(nb) % var % larray3) ) 
775     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % larray3)
776          if ( associated(Agrif_Mygrid % tabvars(nb) % var % larray4) ) 
777     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % larray4)
778          if ( associated(Agrif_Mygrid % tabvars(nb) % var % larray5) ) 
779     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % larray5)
780          if ( associated(Agrif_Mygrid % tabvars(nb) % var % larray6) ) 
781     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % larray6)
782C
783          if ( associated(Agrif_Mygrid % tabvars(nb) % var % carray1) ) 
784     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % carray1)
785          if ( associated(Agrif_Mygrid % tabvars(nb) % var % carray2) ) 
786     &       Deallocate(Agrif_Mygrid % tabvars(nb) % var % carray2)
787      enddo
788C
789      do nb = 1, Agrif_NbVariables
790        Deallocate(Agrif_Mygrid % tabvars(nb) % var)
791      enddo
792C
793      Deallocate(Agrif_Mygrid % tabvars)
794C
795      Deallocate(Agrif_Mygrid)
796C
797      End Subroutine  Agrif_Deallocation 
798C
799      End module Agrif_Util 
Note: See TracBrowser for help on using the repository browser.