source: trunk/SOURCES/relaxation_mod-0.3.f90 @ 23

Last change on this file since 23 was 4, checked in by dumas, 10 years ago

initial import GRISLI trunk

File size: 7.3 KB
Line 
1!> \file relaxation_mod-0.3.f90
2!! Module pour la resolution de l'equation de relaxation.
3!<
4
5!> \namespace RELAXATION_MOD
6!! Module pour la resolution de l'equation de relaxation.
7!! \author Christophe DUMAS
8!! \date fevrier 2000
9!! @note Cette routine est appellee par ICETHICK3
10!! @note Modele couple "ice sheet - ice shelves"
11!<
12
13MODULE RELAXATION_MOD
14
15CONTAINS
16!> SUBROUTINE: relaxation
17!! Routine pour la methode de relaxation
18!! \param NXX     [in]         defini la taille des tableaux
19!! \param NYY     [in]         defini la taille des tableaux
20!! \param Mk      [in]         masks (ice sheet, max, above water, below water, 1)
21!! \param MARINE
22!! \param FLOT
23!! \param DT      [in]         pas de temps court
24!! \param DX      [in]         pas en x
25!! \param vieuxH  [in]         H au pas de temps precedent
26!! \param BM      [in]         mass balance   'o'
27!! \param BMELT   [in]         basal melting  'o'
28!! \param UXBAR   [in]         vertically integrated velocity '>'
29!! \param UYBAR   [in]         vertically integrated velocity '^'
30!! \param H       [out]        ice thickness  'o'
31!! \param HDOT    [out]        ice thickness derivee / t  'o'
32!>
33  subroutine RELAXATION(NXX,NYY,MK,MARINE,FLOT,DT,DX,vieuxH,BM,BMELT,UXBAR,UYBAR,H,HDOT)
34
35    IMPLICIT NONE
36
37
38! declaration des variables en entree
39    INTEGER, intent(in) :: NXX, NYY !< defini la taille des tableaux
40    INTEGER,dimension(NXX,NYY), intent(in) :: MK     !< masks (ice sheet, max, above water, below water, 1)
41    LOGICAL, intent(in) :: MARINE
42    LOGICAL,dimension(NXX,NYY), intent(in) :: FLOT
43    REAL, intent(in) ::  DT                          !< pas de temps court
44    REAL, intent(in) ::  DX                          !< pas en x
45    REAL,dimension(NXX,NYY), intent(in) :: vieuxH    !< H au pas de temps precedent
46    REAL,dimension(NXX,NYY), intent(in) :: BM        !< mass balance   'o'
47    REAL,dimension(NXX,NYY), intent(in) :: BMELT     !< basal melting  'o'
48    REAL,dimension(NXX,NYY), intent(in) :: UXBAR     !< vertically integrated velocity '>'
49    REAL,dimension(NXX,NYY), intent(in) :: UYBAR     !< vertically integrated velocity '^'
50
51
52! declaration des variables en sortie
53    REAL,dimension(NXX,NYY), intent(out) :: H      ! ice thickness  'o'
54    REAL,dimension(NXX,NYY), intent(out) :: HDOT     ! ice thickness derivee / t  'o'
55
56
57! declaration des variables locales
58    INTEGER :: I,J
59    REAL  :: TESTH 
60    REAL,dimension(NXX,NYY) :: ARELAX,BRELAX,CRELAX,DRELAX,ERELAX,FRELAX
61    REAL,dimension(NXX,NYY) :: DELTAH
62    REAL :: RESTE,DELH,VH
63    INTEGER :: ntour
64    integer :: mbord
65    REAL  :: DTSDX 
66    LOGICAL :: STOPP
67
68
69!   print*,'dans relaxation mod'
70    H(:,:)= vieuxH(:,:)
71
72!   attribution des coefficients  arelax ....
73!   ----------------------------------------
74
75    dtsdx=dt/DX
76 
77    do J=2,NYY-1
78       do I=2,NXX-1
79
80
81             FRELAX(I,J)= VIEUXH(I,J)+(BM(I,J)-BMELT(I,J))*DT
82!          selon x
83!                                     ecoulement vers la droite
84             if ((UXBAR(I,J).ge.0.).and.(UXBAR(I+1,J).ge.0.)) then
85                ARELAX(I,J)=-UXBAR(I,J)*dtsdx
86                BRELAX(I,J)=0.
87                CRELAX(I,J)=UXBAR(I+1,J)*dtsdx
88             
89!                                     ecoulement vers la gauche
90             else if ((UXBAR(I,J).le.0.).and.(UXBAR(I+1,J).le.0.)) then
91                ARELAX(I,J)=0.
92                BRELAX(I,J)=UXBAR(I+1,J)*dtsdx
93                CRELAX(I,J)=-UXBAR(I,J)*dtsdx
94             
95!                                     ecoulement divergent
96             else if ((UXBAR(I,J).le.0.).and.(UXBAR(I+1,J).ge.0.)) then
97                ARELAX(I,J)=0.
98                BRELAX(I,J)=0.
99                CRELAX(I,J)=(UXBAR(I+1,J)-UXBAR(I,J))*dtsdx
100             
101!                                     ecoulement convergent
102             else if ((UXBAR(I,J).ge.0.).and.(UXBAR(I+1,J).le.0.)) then
103                ARELAX(I,J)=-UXBAR(I,J)*dtsdx
104                BRELAX(I,J)=UXBAR(I+1,J)*dtsdx
105                CRELAX(I,J)=0.
106             endif
107
108!          selon y
109!                                 ecoulement vers le haut (sens axe y)
110             if ((UYBAR(I,J).ge.0.).and.(UYBAR(I,J+1).ge.0.)) then
111                DRELAX(I,J)=-UYBAR(I,J)*dtsdx
112                ERELAX(I,J)=0.
113                CRELAX(I,J)=1.+(CRELAX(I,J)+(UYBAR(I,J+1)*dtsdx))
114               
115!                                     ecoulement vers le bas
116             else if ((UYBAR(I,J).le.0.).and.(UYBAR(I,J+1).le.0.)) then
117                DRELAX(I,J)=0.
118                ERELAX(I,J)=UYBAR(I,J+1)*dtsdx
119                CRELAX(I,J)=1.+(CRELAX(I,J)-(UYBAR(I,J)*dtsdx))
120           
121!                                     ecoulement divergent
122             else if ((UYBAR(I,J).le.0.).and.(UYBAR(I,J+1).ge.0.)) then
123                DRELAX(I,J)=0.
124                ERELAX(I,J)=0.
125                CRELAX(I,J)=1.+(CRELAX(I,J)+(UYBAR(I,J+1)-UYBAR(I,J))*dtsdx)
126           
127!                                     ecoulement convergent
128             else if ((UYBAR(I,J).ge.0.).and.(UYBAR(I,J+1).le.0.)) then
129                DRELAX(I,J)=-UYBAR(I,J)*dtsdx
130                ERELAX(I,J)=UYBAR(I,J+1)*dtsdx
131                CRELAX(I,J)=1.+CRELAX(I,J)
132           
133             endif
134!          endif
135       end do
136    end do 
137
138! Boucle de relaxation :
139! ----------------------
140
141    STOPP = .false.
142    dtsdx=dt/dx
143    ntour=0
144
145    Do 362 WHILE(.NOT.STOPP)
146       ntour=ntour+1
147     
148       do j=2,NYY-1
149          do i=2,NXX-1
150           
151             RESTE = (((ARELAX(I,J)*H(I-1,J) + BRELAX(I,J)*H(I+1,J)) &
152                       + (DRELAX(I,J)*H(I,J-1) + ERELAX(I,J)*H(I,J+1))) &
153                       + CRELAX(I,J)*H(I,J))- FRELAX(I,J)
154     
155             DELTAH(I,J) = RESTE/CRELAX(I,J)
156!           H(I,J) = H(I,J) - DELTAH(I,J)
157          end do
158       end do
159
160       do j=2,NYY-1
161          do i=2,NXX-1
162             H(I,J) = H(I,J) - DELTAH(I,J)
163          end do
164       end do
165         
166! critere d'arret:
167! ----------------         
168
169       Delh=0
170       Vh=0
171
172       DO j=2,NYY-1
173          DO i=2,NXX-1
174!   write(6,*) I,J,delh,deltah(i,j)
175             Delh=Delh+deltah(i,j)**2
176!            Vh=Vh+h(i,j)**2.
177          END DO
178       END DO
179
180!      testh=SQRT(Delh/Vh)
181       if (delh.gt.0.) then
182          testh=SQRT(Delh)/((NXX-2)*(NYY-2))
183       else
184          testh=0.
185       endif
186       STOPP = (testh.lt.1.E-3).or.(ntour.gt.1000)
187     
188     
189362  Continue
190
191! Conditions aux limites:
192! -----------------------
193
194!   ************ valeurs de H pour les coins ********
195
196       DO i=2,NXX-1
197          H(i,1) = 2.*H(i,2) - H(i,3)
198          H(i,NYY) = 2.*H(i,NYY-1) - H(i,NYY-2)
199       END DO
200       
201       DO J=2,NYY-1
202          H(1,J) = 2.*H(2,j) - H(3,j)
203          H(NXX,J) = 2.*H(NXX-1,j) - H(NXX-2,j)
204       END DO
205
206     
207       h(1,1)=(h(1,2)+h(2,1))/2.
208       Hdot(1,1)=0.
209       h(1,NYY)=(h(1,NYY-1)+h(2,NYY))/2.
210       hdot(1,NYY)=0.
211       h(NXX,1)=(h(NXX,2)+h(NXX-1,1))/2.
212       hdot(nxx,1)=0.
213       h(NXX,NYY)=(h(NXX,NYY-1)+h(NXX-1,NYY))/2.
214       hdot(nxx,nyy)=0.
215! =========================================================================
216
217
218!     open(87,file='test-H')
219!     write(87,*)'time=',time
220
221       do J=2,NYY-1
222          do I=2,NXX-1
223             HDOT(I,J)=(H(i,j)-vieuxH(i,j))/DT 
224
225
226
227!         if (abs(HDOT(I,J)).gt.hdotmax) then
228!  hdotmax=hdot(i,j)
229!  idotmax=i
230! jdotmax=j
231! end if
232
233!         write(87,*)i,j,h(i,j),hdot(i,j)
234          end do
235       end do
236
237
238!         close(87)
239
240
241  end subroutine relaxation
242
243end module relaxation_mod
Note: See TracBrowser for help on using the repository browser.