source: trunk/SOURCES/Hudson_files/output_hudson_mod.f90 @ 334

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

initial import GRISLI trunk

File size: 6.3 KB
Line 
1module  output_hudson
2
3USE module3D_phy
4use sedim_declar
5
6
7implicit none
8
9! 1_initialization
10!------------------
11INTEGER,parameter :: dtt_gliss=20 ! nbr de dtt pour calcul moy glissante
12INTEGER,parameter :: mem=2000 ! nbr de dtt pour garder en memoire pour apres parametrer la fusion basale
13REAL,dimension(dtt_gliss) ::  VOLtot, VOLshelf, oldVOLtot, oldVOLshelf 
14REAL :: VOLtotgliss2 ! moyenne glissante au temps t avec des poids sur les 5 derniers pas de temps avant l'actuel
15REAL :: VOLtotgliss1 ! moyenne glissante au temps t-1 avec des poids sur les 5 derniers pas de temps avant l'actuel
16REAL :: VOLshelfgliss2 !  moyenne glissante au temps tavec des poids sur les 5 derniers pas de temps avant l'actuel
17REAL :: VOLshelfgliss1 !  moyenne glissante au temps t-1avec des poids sur les 5 derniers pas de temps avant l'actuel
18REAL :: deltaVOLtotdt ! variation de volume total sur moy glissante
19REAL :: deltaVOLshelfdt ! variation de volume flottant sur moy glissante
20REAL,DIMENSION(mem) ::  memdeltaVOLtot, memdeltaVOLshelf
21integer ::  NPtot
22integer ::  NPshelf
23integer :: nptemp_tot
24integer ::  NPtemp_sed
25integer :: nbsed
26REAL ::  Hmean_sed
27REAL ::  tbmean_sed
28
29! definition des points particuliers
30integer,parameter  :: nbpoints=7
31integer,parameter :: n1=6 ! nombre de sorties avant les points
32integer,dimension(nbpoints) :: ipos,jpos
33integer,parameter :: nbsortie=nbpoints*4+n1
34
35
36! positions en km
37real,dimension(nbpoints) :: xpos,ypos
38
39! sorties pour ces points
40real,dimension(nbsortie) :: sortie
41
42
43CONTAINS
44
45subroutine init_outshort
46
47!ndisp sorite courte tous les ndisp
48NDISP=100
49VOLtot(:)=0.
50VOLshelf(:)=0.
51
52end subroutine init_outshort
53!VOLtot(:)=0.
54!VOLshelf(:)=0.
55!_________________________________________________________________________
56subroutine shortoutput
57
58oldVOLtot(:)=VOLtot(:)
59oldVOLshelf(:)=VOLshelf(:)
60
61!cdc if (itracebug.eq.1)  call tracebug(' Heino: entree dans routine output_heino')
62
63! 1_initialization
64!------------------
65!VOLtot=0.
66!VOLtot(:)=0.
67!VOLshelf(:)=0.
68!VOLtotgliss2=0.
69!VOLtotgliss1=0.
70!VOLshelfgliss2=0.
71!VOLshelfgliss1=0.
72NPtot=0
73NPshelf=0
74nptemp_tot=0
75NPtemp_sed=0
76Hmean_sed=0.
77tbmean_sed=0.
78nbsed=0.
79! definition des positions des points particuliers en km
80ypos(:)=2000.
81
82xpos(1)=3900.
83xpos(2)=3800.
84xpos(3)=3700.
85xpos(4)=3500.
86xpos(5)=3200.
87xpos(6)=2900.
88xpos(7)=2600.
89
90
91do k=1,nbpoints
92   ipos(k)=nint(xpos(k)/dx*1000.)+1
93   jpos(k)=nint(ypos(k)/dx*1000.)+1
94end do
95
96
97
98!oldVOLtot=eoshift(VOLtot,shift=1,boundary=0.)
99!oldVOLshelf=eoshift(VOLshelf,shift=1,boundary=0.)
100
101! 2_preparing outputs
102!--------------------     
103  do I=1,NX 
104     do J=1,NY
105        NPtot=NPtot+1   ! nombre de points
106        VOLtot(dtt_gliss)=VOLtot(dtt_gliss)+H(I,J)  ! volume total
107        if (flot(i,j))then
108           NPshelf=NPshelf+1
109           VOLshelf(dtt_gliss)=VOLshelf(dtt_gliss)+H(I,J)
110        endif
111        if (t(i,j,nz).ge.tpmp(i,j,nz)) then ! points base temperee
112           nptemp_tot=nptemp_tot+1 !
113           if (mksedim(i,j).ge.2) nptemp_sed=nptemp_sed+1 ! seulement ceux du sediment
114        endif
115        if (mksedim(i,j).ge.2) then
116           Hmean_sed=Hmean_sed+H(i,j) ! epaisseur moyenne zone sediment
117           tbmean_sed=tbmean_sed+(t(i,j,nz)-tpmp(i,j,nz))+273.15
118           nbsed=nbsed+1
119        endif
120    end do
121  end do
122
123!VOLtot=eoshift(VOLtot,shift=1,boundary=0.)
124!VOLshelf=eoshift(VOLshelf,shift=1,boundary=0.)
125
126
127
128VOLtotgliss1=VOLtotgliss2
129
130VOLtotgliss2=(0.1*VOLtot(1)+0.15*VOLtot(2)+0.2*VOLtot(3)+0.25*VOLtot(4)+0.3*VOLtot(5))/12+(0.1*VOLtot(6)+0.15*VOLtot(7)+0.2*VOLtot(8)+0.25*VOLtot(9)+0.3*VOLtot(10))/6+(0.1*VOLtot(11)+0.15*VOLtot(12)+0.2*VOLtot(13)+0.25*VOLtot(14)+VOLtot(15))/4+(0.1*VOLtot(16)+0.15*VOLtot(17)+0.2*VOLtot(18)+0.25*VOLtot(19)+0.3*VOLtot(20))/2
131
132!VOLtotgliss2=0.1*VOLtot(1)+0.15*VOLtot(2)+0.2*VOLtot(3)+0.25*VOLtot(4)+0.3*VOLtot(5)
133deltaVOLtotdt=(VOLtotgliss2-VOLtotgliss1)/dtt
134
135memdeltaVOLtot(mem)=deltaVOLtotdt
136
137
138VOLshelfgliss1=VOLshelfgliss2
139
140VOLshelfgliss2=(0.1*VOLshelf(1)+0.15*VOLshelf(2)+0.2*VOLshelf(3)+0.25*VOLshelf(4)+0.3*VOLshelf(5))/12+(0.1*VOLshelf(6)+0.15*VOLshelf(7)+0.2*VOLshelf(8)+0.25*VOLshelf(9)+0.3*VOLshelf(10))/6+(0.1*VOLshelf(11)+0.15*VOLshelf(12)+0.2*VOLshelf(13)+0.25*VOLshelf(14)+VOLshelf(15))/4+(0.1*VOLshelf(16)+0.15*VOLshelf(17)+0.2*VOLshelf(18)+0.25*VOLshelf(19)+0.3*VOLshelf(20))/2
141
142!VOLshelfgliss2=0.1*VOLshelf(1)+0.15*VOLshelf(2)+0.2*VOLshelf(3)+0.25*VOLshelf(4)+0.3*VOLshelf(5)
143deltaVOLshelfdt=(VOLshelfgliss2-VOLshelfgliss1)/dtt
144
145memdeltaVOLshelf(mem)=deltaVOLshelfdt
146
147!debug
148!print*
149!print*,'output_hudson'
150!print*,time,dtt,dt
151!print*,VOLtot(:)
152!print*,VOLshelf(:)
153!print*,deltaVOLshelfdt, 'deltavolshelfdt'
154!print*,memdeltaVOLshelf(:), 'memdeltavolshelf(:)'
155!print*,memdeltaVOLshelf(1000), 'memdeltavolshelf(1000)'
156!print*,VOLtotgliss1,VOLtotgliss2,VOLshelfgliss1,VOLshelfgliss2
157!print*
158
159
160nbsed=max(nbsed,1)  ! pour eviter une division par 0.
161
162sortie(1)=time
163sortie(2)=VOLtot(19)*dx*dx/1.e15
164!sortie(3)=VOLtot(4)*dx*dx/1.e15
165sortie(3)=VOLshelf(19)*dx*dx/1.e15
166!sortie(4)=oldVOLtot(5)*dx*dx/1.e15
167!sortie(5)=oldVOLtot(4)*dx*dx/1.e15
168!sortie(5)=oldVOLshelf(5)*dx*dx/1.e15
169!sortie(5)=VOLshelf(6)*dx*dx/1.e15
170sortie(4)=deltaVOLtotdt*dx*dx/1.e15
171sortie(5)=deltaVOLshelfdt*dx*dx/1.e15
172!jalv sortie(3)=nptemp_tot*dx*dx/1.e12
173!jalv sortie(4)=hmean_sed/nbsed/1.e3
174!sortie(5)=nptemp_sed*dx*dx/1.e12
175!sortie(6)=tbmean_sed/nbsed
176sortie(6)=VOLtotgliss2*dx*dx/1.e15
177l=n1+1
178do k=1,7
179   i1=ipos(k)
180   j1=jpos(k)
181!   sortie(l)=VOLtotgliss1*dx*dx/1.e15    !sortie 7
182   sortie(l)=memdeltaVOLshelf(1000)    !sortie 7
183   sortie(l+1)=VOLshelfgliss2*dx*dx/1.e15   !sortie 8
184   sortie(l+2)=(memdeltaVOLshelf(1)+memdeltaVOLshelf(500)+memdeltaVOLshelf(1000)+memdeltaVOLshelf(1500))*dx*dx/4.e15   
185!   sortie(l+2)=VOLshelfgliss1*dx*dx/1.e15   !sortie 9
186!   sortie(l)=H(i1,j1)/1000.
187!   sortie(l+1)=T(i1,j1,nz)-tpmp(i1,j1,nz)
188!   sortie(l+2)=chalgliss_maj(i1,j1)/secyear
189!   sortie(l+2)=rog*Hmx(i1,j1)*sdx(i1,j1)*uxbar(i1,j1)
190!   sortie(l+3)=rog*Hmx(i1+1,j1)*sdx(i1+1,j1)*uxbar(i1+1,j1)
191   sortie(l+3)=0.5*(uxbar(i1,j1)+uxbar(i1+1,j1))
192   l=l+4
193end do
194
195!decalage circulaire des variables contenant le volume de glace sur les derniers pas de temps
196VOLtot=eoshift(VOLtot,shift=1,boundary=0.)
197VOLshelf=eoshift(VOLshelf,shift=1,boundary=0.)
198
199memdeltaVOLshelf=eoshift(memdeltaVOLshelf,shift=1,boundary=0.)
200
201
202! 2_writing outputs
203!------------------   
204!     **** short display ****
205
206
207  write(num_ritz,fmt='(34(es14.6,1x))') (sortie(k),k=1,nbsortie)
208 
209
210end subroutine shortoutput
211
212end module output_hudson
Note: See TracBrowser for help on using the repository browser.