source: trunk/SOURCES/Ant45_CISM_files/output_anta_mod-0.4.f90 @ 111

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

initial import GRISLI trunk

File size: 4.2 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!<
12
13module  output_antarcti_mod
14
15USE module3D_phy
16
17
18implicit none
19     
20!real ::  vol ; !integer :: np
21real ::  bmean                        !<
22real ::  accmean                      !< accumulation moyenne
23real ::  ablmean                      !< ablation moyenne
24real ::  calvmean                     !< moyenne calving
25real ::  ablbordmean                  !<
26real ::  bmeltmean                    !< moyenne fusion basale
27real ::  tbmean                       !< temperature basale moyenne
28real ::  tbdotmean                    !< moyenne variation / temps temperature basale
29real ::  vsmean                       !< vitesse de surface moyenne
30!real ::  vsdotmean                    !< moyenne variation / temps vitesse de surface
31!real ::  uzsmean   !!!! utilise ?     !< vitesse verticale de surface moyenne
32real ::  uzsdotmean                   !< moyenne variation / temps vitesse verticale de surface
33real ::  uzkmean                      !< moyenne vitesse verticale de surface
34real ::  hdotmean                     !< moyenne derivee / temps de h
35real ::  bdotmean                     !< moyenne bedrock derive / temps
36real :: volf                          !< volume au dessus de la flottaison
37
38
39CONTAINS
40
41subroutine init_outshort
42
43!ndisp sorite courte tous les ndisp
44NDISP=100
45end subroutine init_outshort
46
47
48
49!_________________________________________________________________________
50subroutine shortoutput
51
52! 1_initialization
53!------------------
54real ::  smax
55      vol=0. 
56      np=0
57      hmax=0. 
58      smax=0.
59      bmean=0. 
60      accmean=0. 
61      ablmean=0. 
62      calvmean=0. 
63      ablbordmean=0.
64      bmeltmean=0.
65      tbmean=0.
66      tbdotmean=0.
67      vsmean=0.
68!      vsdotmean=0.
69!      uzsmean=0.
70      uzsdotmean=0.
71      uzkmean=0.
72      hdotmean=0.
73      bdotmean=0.
74      volf=0.
75 
76! 2_preparing outputs
77!--------------------     
78    do i=1,nx 
79      do j=1,ny
80        if (.not.flot(i,j)) then 
81!       if (h(i,j).gt.1.) then
82          np=np+1
83          vol=vol+h(i,j) 
84
85!        calcul de la hauteur au dessus de la flottaison
86         if (sealevel-B(i,j).le.0.) then    ! socle au dessus du niveau des mers
87               volf=volf+h(i,j)
88         else
89            volf=volf+h(i,j)-row/ro*(sealevel-b(i,j))
90         endif
91
92
93          if (h(i,j).gt.hmax) hmax=h(i,j) 
94          if (s(i,j).gt.smax) smax=s(i,j) 
95          bmean=bm(i,j)+bmean 
96          accmean=acc(i,j)+accmean
97          tbmean=tbmean+t(i,j,nz)
98          tbdotmean=tbdotmean+tbdot(i,j)
99          vsmean=vsmean+sqrt(ux(i,j,1)**2+uy(i,j,1)**2)
100!          vsdotmean=vsdotmean+vsdot(i,j)
101!          uzsmean=uzsmean+uz(i,j,1)
102          uzsdotmean=uzsdotmean+uzsdot(i,j)
103          uzkmean=uzkmean+uzk(i,j)
104          hdotmean=hdotmean+abs(hdot(i,j)) 
105          bdotmean=bdotmean+abs(bdot(i,j)) 
106          bmeltmean=bmeltmean+bmelt(i,j)
107        endif
108        calvmean=calvmean+calv(i,j) 
109        ablbordmean=ablbordmean+ablbord(i,j)
110      end do
111      end do
112
113
114      if (np.ne.0) then
115        hmean=vol/np 
116        vol=vol*dx*dy 
117        volf=volf*dx*dy
118        bmean=bmean/np 
119        accmean=accmean/np 
120        ablmean=bmean-accmean 
121        calvmean=calvmean/np 
122        bmeltmean=bmeltmean/np
123        ablbordmean=ablbordmean/np
124        tbmean=tbmean/np
125        tbdotmean=tbdotmean/np
126        vsmean=vsmean/np
127!        vsdotmean=vsdotmean/np
128!        uzsmean=uzsmean/np
129        uzsdotmean=uzsdotmean/np
130        uzkmean=uzkmean/np
131        hdotmean=hdotmean/np 
132      endif
133
134      bdotmean=bdotmean/nx/ny 
135
136
137! 2_writing outputs
138!------------------   
139!     **** short display ****
140
141        write(num_ritz,903) nt,time,tafor,sealevel,vol,volf,np, &
142          nint(hmean),nint(smax),                    &
143          bmean,tbmean,nint(vsmean),                 &
144!         tbdotmean,vsdotmean,hdotmean,bdotmean,    &
145!          tbdotmean,hdotmean,dt,bmeltmean,accmean
146
147          tbdotmean,hdotmean,dt,bmelt(3,3),accmean 
148
149
150903   format(i8,1x,f0.2,1x,f0.4,1x,f0.2,1x,2(e10.5,1x),i6,1x,i4,1x,i5,1x, &
151             f0.4,1x,f0.3,1x,i3,4(1x,e8.2),1x,f0.4,1x,f0.4) 
152!940   format('%%%% ',a,'   time=',f8.0,' %%%%')
153
154end subroutine shortoutput
155end module  output_antarcti_mod
Note: See TracBrowser for help on using the repository browser.