source: trunk/SOURCES/Snowball_files/output_snowball_mod-0.4.f90 @ 334

Last change on this file since 334 was 237, checked in by aquiquet, 5 years ago

Sealevel is now treated as a 2D variable (sealevel_2d while sealevel remains the eustatic sea level), results should remain identical as sealevel_2d is equal to sealevel in this revision.

File size: 4.4 KB
Line 
1! C. Dumas Nov 2008
2! attention le calcul de MK (ligne d'echouage de GMT) est fait dans masque.F
3! avec des geoplace !!!
4! nouveau calcul des volumes
5
6module  output_snowball_mod
7
8       USE module3D_phy
9
10implicit none
11
12!real ::  vol ; !integer :: np  ! declares dans 3D-physique-gen_mod.f90
13integer :: npflot                     ! nbr points flottants
14real ::  bmean                        ! BM moyen
15real ::  accmean                      ! accumulation moyenne
16real ::  ablmean                      ! ablation moyenne
17real ::  calvmean                     ! moyenne calving
18real ::  ablbordmean                  ! ?
19real ::  bmeltmean                    ! moyenne fusion basale
20real ::  tbmean                       ! temperature basale moyenne
21real ::  tbdotmean                    ! moyenne variation / temps temperature basale
22real ::  vsmean                       ! vitesse de surface moyenne
23real ::  uzsdotmean                   ! moyenne variation / temps vitesse verticale de surface
24real ::  uzkmean                      ! moyenne vitesse verticale de surface
25real ::  hdotmean                     ! moyenne derivee / temps de h
26real ::  volf                         ! volume au dessus de la flottaison
27real ::  volflot                      ! volume ice-shelves
28real ::  Smax                         ! Altitude max de la surface
29
30real ::  Hmin=5.                      ! epaisseur mini de glace pour calcul sur calotte
31
32CONTAINS
33
34subroutine init_outshort
35
36!ndisp sorite courte tous les ndisp
37NDISP=100
38end subroutine init_outshort
39
40
41subroutine shortoutput
42
43! 1_initialization
44!------------------
45      vol=0. 
46      np=0
47      npflot=0
48      hmax=0. 
49      smax=0.
50      bmean=0. 
51      accmean=0. 
52      ablmean=0. 
53      calvmean=0. 
54      ablbordmean=0.
55      bmeltmean=0.
56      tbmean=0.
57      tbdotmean=0.
58      vsmean=0.
59      uzsdotmean=0.
60      uzkmean=0.
61      hdotmean=0.
62      tbdotmean=0.
63      volf=0.
64      volflot=0.
65
66
67! calcul de mk pour les cartes :
68!      where (flot(:,:))
69!         mk(:,:)=1
70!      elsewhere
71!         mk(:,:)=0
72!      endwhere
73 
74! 2_preparing outputs
75!--------------------
76
77      do i=1,nx 
78         do j=1,ny
79            if (h(i,j).gt.Hmin) then
80               if (.not.flot(i,j)) then
81
82                  np=np+1
83                  vol=vol+h(i,j) 
84!        calcul de la hauteur au dessus de la flottaison
85                  if (sealevel_2d(i,j)-B(i,j).le.0.) then    ! socle au dessus du niveau des mers
86                     volf=volf+h(i,j)
87                  else
88                     volf=volf+h(i,j)-row/ro*(sealevel_2d(i,j)-b(i,j))
89                  endif
90
91
92                  hmax=max(hmax,h(i,j)) 
93                  smax=max(smax,s(i,j)) 
94                  bmean=bm(i,j)+bmean 
95                  accmean=acc(i,j)+accmean
96                  tbmean=tbmean+t(i,j,nz)
97                  tbdotmean=tbdotmean+tbdot(i,j)
98                  vsmean=vsmean+sqrt(ux(i,j,1)**2+uy(i,j,1)**2)
99
100                  uzsdotmean=uzsdotmean+uzsdot(i,j)
101                  uzkmean=uzkmean+uzk(i,j)
102                  hdotmean=hdotmean+abs(hdot(i,j)) 
103                 
104                  bmeltmean=bmeltmean+bmelt(i,j)
105               else
106                  npflot=npflot+1
107                  volflot=volflot+H(i,j)
108               endif
109               calvmean=calvmean+calv(i,j) 
110               ablbordmean=ablbordmean+ablbord(i,j)
111            endif
112         end do
113      end do
114
115
116      if (np.ne.0) then
117         hmean=vol/np 
118         vol=vol*dx*dy 
119         volf=volf*dx*dy
120         bmean=bmean/np 
121         accmean=accmean/np 
122         ablmean=bmean-accmean 
123         calvmean=calvmean/np 
124         bmeltmean=bmeltmean/np
125         ablbordmean=ablbordmean/np
126         tbmean=tbmean/np
127         tbdotmean=tbdotmean/np
128         vsmean=vsmean/np
129         uzsdotmean=uzsdotmean/np
130         uzkmean=uzkmean/np
131         hdotmean=hdotmean/np 
132      endif
133
134      volflot=volflot*dx*dy
135
136     
137!      print*,'np,vol', np,vol,volf,volflot,npflot,hmin,hmean
138
139! 2_writing outputs
140!------------------   
141!     **** short display ****
142
143      write(num_ritz,906)   time,tafor,sealevel,vol,volf,np, &
144           nint(hmean),nint(smax),                    &
145           bmean,tbmean,nint(vsmean),                 &
146           tbdotmean,hdotmean,accmean,volflot,npflot                           
147     
148 
149! !! format 900 faux, a reprendre
150
151906 format(f9.1,1x,f4.1,1x,f5.1,1x,e10.4,1x,e10.4,3(1x,i5),1x,f6.3,1x,f6.2,1x,i6,f5.2,1x,f5.2,1x,f5.2,1x,e10.4,1x,i5) 
152
153    end subroutine shortoutput
154
155  end module output_snowball_mod
Note: See TracBrowser for help on using the repository browser.