source: trunk/SOURCES/sortie-hz-multivar.f90 @ 23

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

initial import GRISLI trunk

File size: 5.3 KB
Line 
1!> \file sortie-hz-multivar.f90
2!! Sortie des variables horizontaux.
3!<
4
5!> SUBROUTINE: sortie_hz_multi()
6!! \author ...
7!! \date ...
8!! @note Sortie des variables horizontaux.
9!! @note Appelle rempl_xxx pour les variables qui sont dans module3d_phy
10!! remplace  sortielongue.
11!! @note Used modules:
12!! @note    - use module3D_phy
13!<
14      subroutine sortie_hz_multi()
15 
16! Appelle rempl_xxx pour les variables qui sont dans module3d_phy
17! remplace  sortielongue.
18!
19
20     use module3d_phy
21     use module_choix      ! donne acces a module out_hz
22     implicit none
23     real VVV(nx,ny)       ! variable de travail
24
25! surface, epaisseur, socle
26     if (isort_time(1).eq.1)  call rempli_xxx(1,S)
27     if (isort_time(2).eq.1)  call rempli_xxx(2,H)
28     if (isort_time(3).eq.1)  call rempli_xxx(3,Bsoc)
29
30! masque flottant-pose
31     vvv(:,:)=mk(:,:)
32     if (isort_time(4).eq.1)  call rempli_xxx(4,vvv)
33
34! hdot
35     if (isort_time(5).eq.1)  call rempli_xxx(5,Hdot)
36
37! ============================================================
38! bilan de masse en surface (Bm), Accumulation, ablation,
39
40     if (isort_time(10).eq.1)  call rempli_xxx(10,Bm)
41     if (isort_time(11).eq.1)  call rempli_xxx(11,Acc)
42
43! ablation :
44     VVV(:,:)=BM(:,:)-Acc(:,:)
45     if (isort_time(12).eq.1)  call rempli_xxx(12,VVV)
46
47
48! Calving
49     if (isort_time(13).eq.1)  call rempli_xxx(13,Calv)
50     if (isort_time(14).eq.1)  call rempli_xxx(14,dhdt)
51
52! Temperatures en surface
53     if (isort_time(18).eq.1)  call rempli_xxx(18,Tann)
54     if (isort_time(19).eq.1)  call rempli_xxx(19,Tjuly)
55
56!============================================================
57! Conditions basales
58     VVV(:,:)=T(:,:,nz)-Tpmp(:,:,nz)
59     if (isort_time(20).eq.1)  call rempli_xxx(20,VVV)
60
61! flux geothermique
62     if (isort_time(23).eq.1)  call rempli_xxx(23,ghf)
63     if (isort_time(24).eq.1)  call rempli_xxx(24,phid)
64
65! fusion basale
66     if (isort_time(25).eq.1)  call rempli_xxx(25,bmelt)
67!============================================================
68! vitesse moyenne selon x
69
70    do j=1,ny
71     do i=1,nx
72      if (i.ne.nx) then
73         vvv(i,j)=(uxbar(i,j)+uxbar(i+1,j))/2.
74      else
75         vvv(i,j)=uxbar(i,j)
76      endif
77     end do
78    end do
79 
80  if (isort_time(30).eq.1)  call rempli_xxx(30,VVV)
81
82! vitesse moyenne selon y
83
84    do j=1,ny
85     do i=1,nx
86      if (j.ne.ny) then
87        vvv(i,j)=(uybar(i,j)+uybar(i,j+1))/2
88      else
89        vvv(i,j)=uybar(i,j)
90      endif
91     end do
92    end do
93 
94  if (isort_time(31).eq.1)  call rempli_xxx(31,VVV)
95
96
97  if (isort_time(32).eq.1)  call rempli_xxx(32,uxbar)
98  if (isort_time(33).eq.1)  call rempli_xxx(33,uybar)
99
100   vvv(:,:)=ux(:,:,nz)
101  if (isort_time(34).eq.1)  call rempli_xxx(34,vvv)
102
103   vvv(:,:)=uy(:,:,nz)
104  if (isort_time(35).eq.1)  call rempli_xxx(35,vvv)
105
106!=============================================================
107  if (isort_time(40).eq.1)  call rempli_xxx(40,frotmx)
108  if (isort_time(41).eq.1)  call rempli_xxx(41,frotmy)
109  if (isort_time(42).eq.1)  call rempli_xxx(42,tobmx)
110  if (isort_time(43).eq.1)  call rempli_xxx(43,tobmy)
111  if (isort_time(44).eq.1)  call rempli_xxx(44,taushelf)
112  if (isort_time(45).eq.1)  call rempli_xxx(45,epsxx)
113  if (isort_time(46).eq.1)  call rempli_xxx(46,epsyy)
114  if (isort_time(47).eq.1)  call rempli_xxx(47,epsxy)
115  if (isort_time(48).eq.1)  call rempli_xxx(48,eps)
116!================================================================
117  if (isort_time(50).eq.1)  call rempli_xxx(50,pvi)
118
119!===============================================================
120  if(isort_time(60).eq.1)  call rempli_xxx(60,hwater)
121  if(isort_time(61).eq.1)  call rempli_xxx(61,hdotwater)
122  if(isort_time(62).eq.1)  call rempli_xxx(62,Pgx)
123  if(isort_time(63).eq.1)  call rempli_xxx(63,Pgy)
124  if(isort_time(64).eq.1)  call rempli_xxx(64,kond)
125  if(isort_time(65).eq.1)  call rempli_xxx(65,phiWx)
126  if(isort_time(66).eq.1)  call rempli_xxx(66,phiWy)
127  if(isort_time(68).eq.1)  call rempli_xxx(68,Neffmx)
128  if(isort_time(69).eq.1)  call rempli_xxx(69,Neffmy)
129!===============================================================
130
131!      grounded -> 0, , grzone ->1  ilemx->2   flot->3
132    do j=1,ny
133     do i=1,nx 
134         if (gzmx(i,j)) then     
135            if (ilemx(i,j)) then     ! ile
136              vvv(i,j)=2
137            else                 
138             vvv(i,j)=1        ! grounded zone
139            endif
140         else if (flotmx(i,j)) then ! flottant
141            if (HMX(i,j).gt.1.) then
142              vvv(i,j)=3
143            else
144              vvv(i,j)=4
145            endif
146         else                     ! pose
147            vvv(i,j)=0
148         endif
149        end do
150      end do
151   if(isort_time(70).eq.1)  call rempli_xxx(70,vvv)
152    do j=1,ny
153     do i=1,nx 
154        if (gzmy(i,j)) then
155            if (ilemy(i,j)) then
156              vvv(i,j)=2
157            else
158             vvv(i,j)=1
159            endif
160         else if (flotmy(i,j)) then
161            if (HMY(i,j).gt.1.) then
162              vvv(i,j)=3 
163            else
164              vvv(i,j)=4 
165            endif
166         else
167            vvv(i,j)=0
168         endif
169        end do
170       end do
171   if(isort_time(71).eq.1)  call rempli_xxx(71,vvv)
172
173! frontfacex et frontfacey
174 vvv(:,:)=frontfacex(:,:)
175   if(isort_time(72).eq.1)  call rempli_xxx(72,vvv)
176 vvv(:,:)=frontfacey(:,:)
177   if(isort_time(73).eq.1)  call rempli_xxx(73,vvv)
178
179!=============================================================
180 return
181 end subroutine sortie_hz_multi
Note: See TracBrowser for help on using the repository browser.