source: trunk/SOURCES/Greenmint40_files/output_green_mod-0.4.f90 @ 123

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

initial import GRISLI trunk

File size: 4.3 KB
RevLine 
[4]1!> \file output_green_mod-0.4.f90
2!! Module d'ecriture des output
3!<
4
5!> \namespace output_greenmint_mod
6!! Module d'ecriture des output
7!! \author ...
8!! \date ...
9!! @note Used module
10!! @note   - use module3D_phy
11!<
12
13module  output_greenmint_mod
14
15use module3d_phy
16
17
18implicit none
19     
20
21real ::  bmean                        !< bilan de masse moyen
22real ::  accmean                      !< accumulation moyenne
23real ::  ablmean                      !< ablation moyenne
24real ::  calvmean                     !< moyenne calving
25real ::  ablbordmean                  !< ablation sur les bords
26real ::  bmeltmean                    !< moyenne fusion basale
27real ::  tbmean                       !< temperature basale moyenne
28real ::  vsmean                       !< vitesse de surface moyenne
29real ::  hdotmean                     !< moyenne derivee / temps de h
30real ::  bdotmean                     !< moyenne bedrock derive / temps
31real ::  volf                         !< volume au dessus de la flottaison
32real ::  volg                         !< volume glace posee
33real ::  vol_shelf                    !< volume ice shelf
34integer :: npg                        !< nombre de points englaces-poses
35integer :: nf                         !< nombre de points englaces-flottants
36integer :: nabl                       !< nombre de points zone d'ablation
37
38
39CONTAINS
40
41subroutine init_outshort
42
43ndisp=100                             ! ndisp sortie courte tous les ndisp
44
45end subroutine init_outshort
46
47
48
49!_________________________________________________________________________
50subroutine shortoutput
51
52! 1_initialization
53!------------------
54real ::  smax                         ! pour calculer la surface  max
55real ::  hmax                         ! pour calculer l'epaisseur max
56     
57npg=0
58nf=0
59nabl=0
60
61hmax=0. 
62smax=0.
63bmean=0. 
64accmean=0. 
65ablmean=0. 
66calvmean=0. 
67ablbordmean=0.
68bmeltmean=0.
69tbmean=0.
70hdotmean=0.
71bdotmean=0.
72volf=0.
73volg=0. 
74vol_shelf=0.
75
76! 2_preparing outputs
77!--------------------     
78do j=1,ny
79   do i=1,nx 
80     
81pose: if (.not.flot(i,j)) then        ! glace posee
82         if (h(i,j).gt.1.) then       ! points englaces
83          npg=npg+1
84          volg=volg+h(i,j) 
85
86!        nombre de points dans la zone d'ablation
87         if (bm(i,j).lt.0.) nabl=nabl+1
88
89!        calcul de la hauteur au dessus de la flottaison
90
91         if (sealevel-B(i,j).le.0.) then    ! socle au dessus du niveau des mers
92               volf=volf+h(i,j)
93         else
94            volf=volf+h(i,j)-row/ro*(sealevel-b(i,j))
95         endif
96
97!         recherche de l'epaisseur et surface max
98         hmax=max(h(i,j),hmax)
99         smax=max(s(i,j),smax) 
100         bmean=bm(i,j)+bmean 
101         accmean=acc(i,j)+accmean
102         tbmean=tbmean+t(i,j,nz)
103         vsmean=vsmean+sqrt(ux(i,j,1)**2+uy(i,j,1)**2)
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
111     else                           ! glace flottante
112        if (h(i,j).gt.1.) then       ! points englaces
113           nf=nf+1
114           vol_shelf=vol_shelf+H(i,j)
115        end if
116     end if pose
117
118
119 end do
120end do
121
122! moyennes
123      if (npg.ne.0) then
124        hmean=volg/npg 
125        bmean=bmean/npg 
126        accmean=accmean/npg 
127        ablmean=bmean-accmean 
128        calvmean=calvmean/npg 
129        bmeltmean=bmeltmean/npg
130        ablbordmean=ablbordmean/npg
131        tbmean=tbmean/npg
132        vsmean=vsmean/npg
133        hdotmean=hdotmean/npg 
134        bdotmean=bdotmean/npg
135      endif
136
137        volg=volg*dx*dy 
138        volf=volf*dx*dy
139        vol_shelf=vol_shelf*dx*dy
140
141
142! 2_writing outputs
143!------------------   
144
145        write(num_ritz,904)  nt,time,tafor,sealevel,         &        ! temps, forcages
146                             volg,volf,vol_shelf,            &        ! volumes 5,6,7
147                             npg*dx*dy,nf*dx*dy,nabl*dx*dy,  &        ! surfaces 8,9,10
148                             bmean,accmean,ablmean,hdotmean, &        ! bilans 11,12
149                             nint(hmean),nint(smax),         &        ! epaisseurs
150                             nint(vsmean),tbmean                      ! vitesse,tbmean
151
152
153904   format(i8,1x,f0.2,1x,f0.4,1x,f0.2,1x,10(es11.4,1x),3(i0,1x),f0.3)
154
155end subroutine shortoutput
156end module  output_greenmint_mod
Note: See TracBrowser for help on using the repository browser.