source: trunk/SOURCES/Ant15_CISM_files/output_anta_mod-0.4.f90 @ 237

Last change on this file since 237 was 237, checked in by aquiquet, 6 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.3 KB
Line 
1!> \file output_anta_mod-0.4.f90
2!! Module de
3!<
4
5!> \namespace output_antarcti_mod
6!! Module de
7!! \author ...
8!! \date ...
9!! @note Used module
10!! @note   - use module3D_phy
11!<
12module  output_antarcti_mod
13
14USE module3D_phy
15
16
17implicit none
18     
19!real ::  vol ; !integer :: np
20real ::  bmean                        !<
21real ::  accmean                      !< accumulation moyenne
22real ::  ablmean                      !< ablation moyenne
23real ::  calvmean                     !< moyenne calving
24real ::  ablbordmean                  !<
25real ::  bmeltmean                    !< moyenne fusion basale
26real ::  tbmean                       !< temperature basale moyenne
27real ::  tbdotmean                    !< moyenne variation / temps temperature basale
28real ::  vsmean                       !< vitesse de surface moyenne
29!real ::  vsdotmean                    !< moyenne variation / temps vitesse de surface
30!real ::  uzsmean   !!!! utilise ?     !< vitesse verticale de surface moyenne
31real ::  uzsdotmean                   !< moyenne variation / temps vitesse verticale de surface
32real ::  uzkmean                      !< moyenne vitesse verticale de surface
33real ::  hdotmean                     !< moyenne derivee / temps de h
34real ::  bdotmean                     !< moyenne bedrock derive / temps
35real :: volf                          !< volume au dessus de la flottaison
36
37
38CONTAINS
39
40subroutine init_outshort
41
42!ndisp sorite courte tous les ndisp
43NDISP=100
44end subroutine init_outshort
45
46
47
48!_________________________________________________________________________
49subroutine shortoutput
50
51! 1_initialization
52!------------------
53real ::  smax
54      vol=0. 
55      np=0
56      hmax=0. 
57      smax=0.
58      bmean=0. 
59      accmean=0. 
60      ablmean=0. 
61      calvmean=0. 
62      ablbordmean=0.
63      bmeltmean=0.
64      tbmean=0.
65      tbdotmean=0.
66      vsmean=0.
67!      vsdotmean=0.
68!      uzsmean=0.
69      uzsdotmean=0.
70      uzkmean=0.
71      hdotmean=0.
72      bdotmean=0.
73      volf=0.
74 
75! 2_preparing outputs
76!--------------------     
77    do i=1,nx 
78      do j=1,ny
79        if (.not.flot(i,j)) then 
80!       if (h(i,j).gt.1.) then
81          np=np+1
82          vol=vol+h(i,j) 
83
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          if (h(i,j).gt.hmax) hmax=h(i,j) 
93          if (s(i,j).gt.smax) 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!          vsdotmean=vsdotmean+vsdot(i,j)
100!          uzsmean=uzsmean+uz(i,j,1)
101          uzsdotmean=uzsdotmean+uzsdot(i,j)
102          uzkmean=uzkmean+uzk(i,j)
103          hdotmean=hdotmean+abs(hdot(i,j)) 
104          bdotmean=bdotmean+abs(bdot(i,j)) 
105          bmeltmean=bmeltmean+bmelt(i,j)
106        endif
107        calvmean=calvmean+calv(i,j) 
108        ablbordmean=ablbordmean+ablbord(i,j)
109      end do
110      end do
111
112
113      if (np.ne.0) then
114        hmean=vol/np 
115        vol=vol*dx*dy 
116        volf=volf*dx*dy
117        bmean=bmean/np 
118        accmean=accmean/np 
119        ablmean=bmean-accmean 
120        calvmean=calvmean/np 
121        bmeltmean=bmeltmean/np
122        ablbordmean=ablbordmean/np
123        tbmean=tbmean/np
124        tbdotmean=tbdotmean/np
125        vsmean=vsmean/np
126!        vsdotmean=vsdotmean/np
127!        uzsmean=uzsmean/np
128        uzsdotmean=uzsdotmean/np
129        uzkmean=uzkmean/np
130        hdotmean=hdotmean/np 
131      endif
132
133      bdotmean=bdotmean/nx/ny 
134
135
136! 2_writing outputs
137!------------------   
138!     **** short display ****
139
140        write(num_ritz,903) nt,time,tafor,sealevel,vol,volf,np, &
141          nint(hmean),nint(smax),                    &
142          bmean,tbmean,nint(vsmean),                 &
143!         tbdotmean,vsdotmean,hdotmean,bdotmean,    &
144!          tbdotmean,hdotmean,dt,bmeltmean,accmean
145
146          tbdotmean,hdotmean,dt,bmelt(3,3),accmean 
147
148
149903   format(i8,1x,f0.2,1x,f0.4,1x,f0.2,1x,2(e10.5,1x),i6,1x,i4,1x,i5,1x, &
150             f0.4,1x,f0.3,1x,i3,4(1x,e8.2),1x,f0.4,1x,f0.4) 
151!940   format('%%%% ',a,'   time=',f8.0,' %%%%')
152
153end subroutine shortoutput
154end module  output_antarcti_mod
Note: See TracBrowser for help on using the repository browser.