source: trunk/SOURCES/Greeneem_files/output_greeneem_mod-0.4.f90 @ 4

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

initial import GRISLI trunk

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