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.
agrif_top_update.F90 in branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/NST_SRC – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/NST_SRC/agrif_top_update.F90 @ 3432

Last change on this file since 3432 was 2715, checked in by rblod, 13 years ago

First attempt to put dynamic allocation on the trunk

  • Property svn:keywords set to Id
File size: 3.2 KB
Line 
1#define TWO_WAY
2
3MODULE agrif_top_update
4
5#if defined key_agrif && defined key_top
6   USE par_oce
7   USE oce
8   USE dom_oce
9   USE agrif_oce
10   USE trc
11
12   IMPLICIT NONE
13   PRIVATE
14
15   PUBLIC Agrif_Update_Trc
16
17   INTEGER, PUBLIC :: nbcline_trc = 0
18
19   !!----------------------------------------------------------------------
20   !! NEMO/NST 3.3 , NEMO Consortium (2010)
21   !! $Id$
22   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
23   !!----------------------------------------------------------------------
24
25   CONTAINS
26
27   SUBROUTINE Agrif_Update_Trc( kt )
28      !!---------------------------------------------
29      !!   *** ROUTINE Agrif_Update_Trc ***
30      !!---------------------------------------------
31      USE wrk_nemo, ONLY: wrk_in_use, wrk_not_released
32      USE wrk_nemo, ONLY: wrk_4d_1
33      !!
34      INTEGER, INTENT(in) :: kt
35      REAL(wp), POINTER, DIMENSION(:,:,:,:) :: ztra
36
37 
38      IF ((Agrif_NbStepint() .NE. (Agrif_irhot()-1)).AND.(kt /= 0)) RETURN
39
40#if defined TWO_WAY
41      IF( wrk_in_use(4, 1) ) THEN
42         CALL ctl_stop('Agrif_Update_trc : requested workspace arrays unavailable')
43         RETURN
44      ENDIF
45      ztra =>  wrk_4d_1(:,:,:,jptra)
46
47      Agrif_UseSpecialValueInUpdate = .TRUE.
48      Agrif_SpecialValueFineGrid = 0.
49 
50     IF (MOD(nbcline_trc,nbclineupdate) == 0) THEN
51         CALL Agrif_Update_Variable(ztra,trn_id, procname=updateTRC)
52      ELSE
53         CALL Agrif_Update_Variable(ztra,trn_id,locupdate=(/0,2/), procname=updateTRC)
54      ENDIF
55
56      Agrif_UseSpecialValueInUpdate = .FALSE.
57      nbcline_trc = nbcline_trc + 1
58
59      IF( wrk_not_released(4, 1) ) THEN
60         CALL ctl_stop('Agrif_Update_trc : failed to release workspace arrays.')
61         RETURN
62      ENDIF
63#endif
64
65   END SUBROUTINE Agrif_Update_Trc
66
67   SUBROUTINE updateTRC(tabres,i1,i2,j1,j2,k1,k2,l1,l2,before)
68      !!---------------------------------------------
69      !!   *** ROUTINE UpdateTrc ***
70      !!---------------------------------------------
71#  include "domzgr_substitute.h90"
72
73      INTEGER, INTENT(in) :: i1,i2,j1,j2,k1,k2,l1,l2
74      REAL, DIMENSION(i1:i2,j1:j2,k1:k2,l1:l2), INTENT(inout) :: tabres
75      LOGICAL, INTENT(in) :: before
76   
77      INTEGER :: ji,jj,jk,jl
78
79         IF (before) THEN
80            DO jl=l1,l2
81               DO jk=k1,k2
82                  DO jj=j1,j2
83                     DO ji=i1,i2
84                        tabres(ji,jj,jk,jl) = trn(ji,jj,jk,jl)
85                     ENDDO
86                  ENDDO
87               ENDDO
88            ENDDO
89         ELSE
90            DO jl=l1,l2
91               DO jk=k1,k2
92                  DO jj=j1,j2
93                     DO ji=i1,i2
94                        IF (tabres(ji,jj,jk,jl).NE.0.) THEN
95                           trn(ji,jj,jk,jl) = tabres(ji,jj,jk,jl) * tmask(ji,jj,jk)
96                        ENDIF
97                     ENDDO
98                  ENDDO
99               ENDDO
100            ENDDO
101         ENDIF
102
103   END SUBROUTINE updateTRC
104
105#else
106CONTAINS
107   SUBROUTINE agrif_top_update_empty
108      !!---------------------------------------------
109      !!   *** ROUTINE agrif_Top_update_empty ***
110      !!---------------------------------------------
111      WRITE(*,*)  'agrif_top_update : You should not have seen this print! error?'
112   END SUBROUTINE agrif_top_update_empty
113#endif
114END Module agrif_top_update
Note: See TracBrowser for help on using the repository browser.