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

source: trunk/AGRIF/AGRIF_FILES/modmask.F @ 662

Last change on this file since 662 was 662, checked in by opalod, 17 years ago

RB: update Agrif internal routines with a new update scheme and performance improvment

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 13.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_Mask
26C
27      Module Agrif_Mask
28C
29CCC   Description:
30CCC   Module for masks
31C
32C     Modules used: 
33C
34      Use Agrif_Types       
35C
36      IMPLICIT NONE
37      Integer, Parameter :: MaxSearch = 5
38C
39      CONTAINS
40C     Define procedures contained in this module
41C
42C     **************************************************************************
43C     Subroutine Agrif_CheckMasknD
44C     **************************************************************************
45C       
46      Subroutine Agrif_CheckMasknD(tempP,parent,pbtab,petab,ppbtab,
47     &               ppetab,noraftab,nbdim)
48C
49CCC   Description:
50CCC   Subroutine called in the procedure Agrif_InterpnD to recalculate the value
51CCC   of the parent grid variable when this one is equal to Agrif_SpecialValue. 
52C
53C     Declarations:
54C
55       
56C
57C     Arrays arguments     
58      INTEGER :: nbdim
59      INTEGER,DIMENSION(nbdim) :: pbtab  ! Limits of the parent grid used 
60      INTEGER,DIMENSION(nbdim) :: petab  ! interpolation of the child grid
61      LOGICAL,DIMENSION(nbdim) :: noraftab
62      INTEGER,DIMENSION(nbdim) :: ppbtab,ppetab
63C
64C     Pointer argument
65      TYPE(AGRIF_PVARIABLE) :: tempP  ! Part of the parent grid used for
66                                      ! the interpolation of the child grid                     
67C     Data TYPE argument                                   
68      TYPE(AGRIF_PVARIABLE) :: parent      ! The parent grid
69C
70C     Local scalar
71      INTEGER                   :: i0,j0,k0,l0,m0,n0
72C     
73C     Local arrays
74C
75C     
76      SELECT CASE (nbdim)
77      CASE (1)
78         do i0 = pbtab(1),petab(1)
79         IF (tempP%var%array1(i0)
80     &                        == Agrif_SpecialValue) Then
81            Call CalculNewValTempP((/i0/),
82     &                             tempP,parent,
83     &                             ppbtab,ppetab,
84     &                             noraftab,nbdim)
85         ENDIF
86         enddo
87      CASE (2)
88         do j0 = pbtab(2),petab(2)
89         do i0 = pbtab(1),petab(1)
90         IF (tempP%var%array2(i0,j0)
91     &                        == Agrif_SpecialValue) Then
92            Call CalculNewValTempP((/i0,j0/),
93     &                             tempP,parent,
94     &                             ppbtab,ppetab,
95     &                             noraftab,nbdim)
96         ENDIF
97         enddo 
98         enddo
99      CASE (3)
100         do k0 = pbtab(3),petab(3)
101         do j0 = pbtab(2),petab(2)
102         do i0 = pbtab(1),petab(1)
103         IF (tempP%var%array3(i0,j0,k0)
104     &                        == Agrif_SpecialValue) Then
105            Call CalculNewValTempP((/i0,j0,k0/),
106     &                             tempP,parent,
107     &                             ppbtab,ppetab,
108     &                             noraftab,nbdim)
109         ENDIF
110         enddo
111         enddo 
112         enddo
113      CASE (4)
114         do l0 = pbtab(4),petab(4)
115         do k0 = pbtab(3),petab(3)
116         do j0 = pbtab(2),petab(2)
117         do i0 = pbtab(1),petab(1)
118         IF (tempP%var%array4(i0,j0,k0,l0) 
119     &                        == Agrif_SpecialValue) Then
120            Call CalculNewValTempP((/i0,j0,k0,l0/),
121     &                             tempP,parent,
122     &                             ppbtab,ppetab,
123     &                             noraftab,nbdim)
124         ENDIF
125         enddo
126         enddo
127         enddo 
128         enddo
129      CASE (5)
130         do m0 = pbtab(5),petab(5)
131         do l0 = pbtab(4),petab(4)
132         do k0 = pbtab(3),petab(3)
133         do j0 = pbtab(2),petab(2)
134         do i0 = pbtab(1),petab(1)
135         IF (tempP%var%array5(i0,j0,k0,l0,m0) 
136     &                       == Agrif_SpecialValue) Then
137            Call CalculNewValTempP((/i0,j0,k0,l0,m0/),
138     &                             tempP,parent,
139     &                             ppbtab,ppetab,
140     &                             noraftab,nbdim)
141         ENDIF
142         enddo
143         enddo
144         enddo 
145         enddo
146         enddo
147      CASE (6)
148         do n0 = pbtab(6),petab(6)
149         do m0 = pbtab(5),petab(5)
150         do l0 = pbtab(4),petab(4)
151         do k0 = pbtab(3),petab(3)
152         do j0 = pbtab(2),petab(2)
153         do i0 = pbtab(1),petab(1)
154         IF (tempP%var%array6(i0,j0,k0,l0,m0,n0) 
155     &                       == Agrif_SpecialValue) Then
156            Call CalculNewValTempP((/i0,j0,k0,l0,m0,n0/),
157     &                             tempP,parent,
158     &                             ppbtab,ppetab,
159     &                             noraftab,nbdim)
160         ENDIF
161         enddo
162         enddo
163         enddo
164         enddo 
165         enddo
166         enddo
167      END SELECT
168C
169C     
170C     
171      End Subroutine Agrif_CheckMasknD
172C
173C
174C     **************************************************************************
175C     Subroutine CalculNewValTempP
176C     **************************************************************************
177C       
178      Subroutine CalculNewValTempP(indic,
179     &               tempP,parent,ppbtab,
180     &               ppetab,noraftab,nbdim)
181C
182CCC   Description:
183CCC   Subroutine called in the procedure Agrif_InterpnD to recalculate the value
184CCC   of the parent grid variable when this one is equal to Agrif_SpecialValue. 
185C
186C     Declarations:
187C
188       
189C
190C     Arrays arguments     
191      INTEGER :: nbdim
192      INTEGER,DIMENSION(nbdim) :: indic
193      LOGICAL,DIMENSION(nbdim) :: noraftab
194      INTEGER,DIMENSION(nbdim) :: ppbtab,ppetab
195C
196C     Pointer argument
197      TYPE(AGRIF_PVARIABLE) :: tempP  ! Part of the parent grid used for
198                                      ! the interpolation of the child grid                     
199C     Data TYPE argument                                   
200      TYPE(AGRIF_PVARIABLE) :: parent      ! The parent grid
201C
202C     Local scalar
203      INTEGER                  :: i,ii,iii,jj,kk,ll,mm,nn 
204      INTEGER,DIMENSION(nbdim) :: imin,imax,idecal
205      INTEGER                  :: Nbvals
206      REAL                     :: Res
207      REAL                     :: ValParent
208      INTEGER                  :: ValMax
209      LOGICAL                  :: firsttest
210C     
211C     Local arrays     
212C
213      ValMax = 1
214      do iii = 1 , nbdim
215         IF (.NOT.noraftab(iii)) THEN
216         ValMax = max(ValMax,ppetab(iii)-indic(iii))
217         ValMax = max(ValMax,indic(iii)-ppbtab(iii))
218         ENDIF
219      enddo
220C
221      Valmax = min(Valmax,MaxSearch)
222C
223      imin = indic
224      imax = indic
225C
226         i = 1
227         firsttest = .TRUE.
228C
229         do While(i <= ValMax)
230C
231         IF ((i == 1).AND.(firsttest)) i = Valmax
232
233            do iii = 1 , nbdim
234               if (.NOT.noraftab(iii)) then
235                  imin(iii) = max(indic(iii) - i,ppbtab(iii))
236                  imax(iii) = min(indic(iii) + i,ppetab(iii))
237                  if (firsttest) then               
238                  if (indic(iii).GT.ppbtab(iii)) then
239
240                     idecal = indic
241                     idecal(iii) = idecal(iii)-1
242                     SELECT CASE(nbdim)
243                     CASE (1)
244                        if (tempP%var%array1(idecal(1)
245     &                            ) == Agrif_SpecialValue) then
246                           imin(iii) = imax(iii)
247                        endif                     
248                     CASE (2)
249                        if (tempP%var%array2(idecal(1),
250     &            idecal(2)) == Agrif_SpecialValue) then
251                           imin(iii) = imax(iii)
252                        endif
253                     CASE (3)
254                        if (tempP%var%array3(idecal(1),
255     &            idecal(2),idecal(3)) 
256     &                               == Agrif_SpecialValue) then
257                           imin(iii) = imax(iii)
258                        endif 
259                     CASE (4)
260                        if (tempP%var%array4(idecal(1),
261     &            idecal(2),idecal(3),idecal(4)) 
262     &                               == Agrif_SpecialValue) then
263                           imin(iii) = imax(iii)
264                        endif     
265                     CASE (5)
266                        if (tempP%var%array5(idecal(1),
267     &            idecal(2),idecal(3),idecal(4),idecal(5)) 
268     &                               == Agrif_SpecialValue) then
269                           imin(iii) = imax(iii)
270                        endif 
271                     CASE (6)
272                        if (tempP%var%array6(idecal(1),
273     &            idecal(2),idecal(3),idecal(4),idecal(5),idecal(6)) 
274     &                               == Agrif_SpecialValue) then
275                           imin(iii) = imax(iii)
276                        endif                                                                                           
277                     END SELECT
278                  endif
279                  endif
280               endif           
281            enddo
282C
283            Res = 0.
284            Nbvals = 0
285C
286            SELECT CASE(nbdim)
287            CASE (1)
288               do ii = imin(1),imax(1)
289                    ValParent = parent%var%array1(ii)
290                    if ( ValParent .NE. Agrif_SpecialValue) then
291                        Res = Res + ValParent
292                        Nbvals = Nbvals + 1
293                    endif
294               enddo
295C
296            CASE (2)
297               do jj = imin(2),imax(2)
298               do ii = imin(1),imax(1)
299                    ValParent = parent%var%array2(ii,jj)
300                    if ( ValParent .NE. Agrif_SpecialValue) then
301                        Res = Res + ValParent
302                        Nbvals = Nbvals + 1
303                    endif
304               enddo 
305               enddo
306               
307            CASE (3)
308               do kk = imin(3),imax(3)
309               do jj = imin(2),imax(2)
310               do ii = imin(1),imax(1)
311                    ValParent = parent%var%array3(ii,jj,kk)
312                    if ( ValParent .NE. Agrif_SpecialValue) then
313                        Res = Res + ValParent
314                        Nbvals = Nbvals + 1
315                    endif
316                        enddo
317                  enddo 
318               enddo
319
320            CASE (4)
321               do ll = imin(4),imax(4)
322               do kk = imin(3),imax(3)
323               do jj = imin(2),imax(2)
324               do ii = imin(1),imax(1)
325                    ValParent = parent%var%array4(ii,jj,kk,ll)
326                    if ( ValParent .NE. Agrif_SpecialValue) then
327                        Res = Res + ValParent
328                        Nbvals = Nbvals + 1
329                    endif
330                              enddo
331                        enddo
332                  enddo 
333               enddo
334
335            CASE (5)
336               do mm = imin(5),imax(5)
337               do ll = imin(4),imax(4)
338               do kk = imin(3),imax(3)
339               do jj = imin(2),imax(2)
340               do ii = imin(1),imax(1)
341                    ValParent = parent%var%array5(ii,jj,kk,ll,mm)
342                    if ( ValParent .NE. Agrif_SpecialValue) then
343                        Res = Res + ValParent
344                        Nbvals = Nbvals + 1
345                    endif
346                                    enddo
347                              enddo
348                        enddo
349                  enddo 
350               enddo
351
352            CASE (6)
353               do nn = imin(6),imax(6)
354               do mm = imin(5),imax(5)
355               do ll = imin(4),imax(4)
356               do kk = imin(3),imax(3)
357               do jj = imin(2),imax(2)
358               do ii = imin(1),imax(1)
359                    ValParent = parent%var%array6(ii,jj,kk,ll,mm,nn)
360                    if ( ValParent .NE. Agrif_SpecialValue) then
361                        Res = Res + ValParent
362                        Nbvals = Nbvals + 1
363                    endif
364                                          enddo
365                                    enddo
366                              enddo
367                        enddo
368                  enddo 
369               enddo
370
371            END SELECT
372C
373C
374           
375            if (Nbvals.GT.0) then
376              if (firsttest) then
377                   firsttest = .FALSE.
378                   i=1
379                   cycle
380              endif
381            SELECT CASE(nbdim)
382            CASE (1)             
383              tempP%var%array1(indic(1)) 
384     &           = Res/Nbvals
385            CASE (2)
386              tempP%var%array2(indic(1),
387     &                            indic(2)) = Res/Nbvals
388            CASE (3)
389              tempP%var%array3(indic(1),
390     &                            indic(2),indic(3)) = Res/Nbvals
391            CASE (4)
392              tempP%var%array4(indic(1),
393     &                            indic(2),indic(3),indic(4))
394     &                = Res/Nbvals
395            CASE (5)
396              tempP%var%array5(indic(1),
397     &                            indic(2),indic(3),indic(4),
398     &                   indic(5)) = Res/Nbvals
399            CASE (6)
400              tempP%var%array6(indic(1),
401     &                            indic(2),indic(3),indic(4),
402     &                           indic(5),indic(6)) = Res/Nbvals
403            END SELECT
404              exit
405            else
406               if (firsttest) exit
407               i = i + 1                     
408            endif
409          enddo           
410C     
411      End Subroutine CalculNewValTempP
412C
413C
414      End Module Agrif_Mask       
Note: See TracBrowser for help on using the repository browser.