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

Last change on this file since 102 was 102, checked in by dumas, 7 years ago

Update closed water cycle | H = 1m on sea suppressed

File size: 7.6 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
22!!$real ::  bmean                        !< bilan de masse moyen
23!!$real ::  accmean                      !< accumulation moyenne
24!!$real ::  ablmean                      !< ablation moyenne
25!!$real ::  calvmean                     !< moyenne calving
26!!$real ::  ablbordmean                  !< ablation sur les bords
27!!$real ::  bmeltmean                    !< moyenne fusion basale
28!!$real ::  tbmean                       !< temperature basale moyenne
29!!$real ::  vsmean                       !< vitesse de surface moyenne
30!!$real ::  hdotmean                     !< moyenne derivee / temps de h
31!!$real ::  bdotmean                     !< moyenne bedrock derive / temps
32!!$real ::  volf                         !< volume au dessus de la flottaison
33!!$real ::  volg                         !< volume glace posee
34!!$real ::  vol_shelf                    !< volume ice shelf
35!!$integer :: npg                        !< nombre de points englaces-poses
36!!$integer :: nf                         !< nombre de points englaces-flottants
37!!$integer :: nabl                       !< nombre de points zone d'ablation
38integer,parameter :: nbregion=2       ! nbr de zones geographiques
39logical,dimension(nx,ny,nbregion) :: mask_cal ! masque regions calotte
40integer, dimension(nx,ny) :: write_mask
41
42CONTAINS
43
44subroutine init_outshort
45
46ndisp=100                             ! ndisp sortie courte tous les ndisp
47
48mask_cal(:,:,:)=.false.
49mask_cal(:,:,1)=.true.
50sum_H_old = sum(H(:,:),mask=ice(:,:)==1)
51do j=1,ny
52   do i=1,nx
53! -- Groenland
54      IF ( (((xlong(i,j).ge.290).AND.(xlong(i,j).le.350)).AND. &
55           ((ylat(i,j).ge.79.5).AND.(ylat(i,j).le.85))).OR.      &
56           (((xlong(i,j).ge.286).AND.(xlong(i,j).lt.345)).AND. &
57           ((ylat(i,j).ge.75).AND.(ylat(i,j).le.79.5))).OR.      &
58           (((xlong(i,j).ge.300).AND.(xlong(i,j).le.345)).AND. &
59           ((ylat(i,j).ge.67).AND.(ylat(i,j).le.75))).OR.    &
60           (((xlong(i,j).ge.305).AND.(xlong(i,j).le.330)).AND. &
61           ((ylat(i,j).ge.55).AND.(ylat(i,j).le.67))) ) mask_cal(i,j,2)=.true.
62   enddo
63enddo
64!!!! Attention au formatage !!!!
65WRITE(num_ritz, '(a134)')         "! greeneem15 :   time, isvol,   inp,isvolf,isvol_shelf,inf,isacc,isabl,isablbord,ablatot,iscalv,isbm,Tjulymean,Hmean,Hmax, nabl,  nacc"
66WRITE(num_ritz, '(a134)')         "! IS         :      1      2      3      4      5      6      7      8      9     10     11     12     13     14     15     16     17 "
67WRITE(num_ritz, '(a21,16(5x,i2))')'! Greenland  :       ',((i),i=18,33)
68end subroutine init_outshort
69
70
71
72!_________________________________________________________________________
73subroutine shortoutput
74 
75
76  real,dimension(nbregion) :: isvol ! vol calotte posee
77  real,dimension(nbregion) :: isvolf ! vol calotte au-dessus flottaison
78  real,dimension(nbregion) :: isvol_shelf ! vol calotte au-dessus flottaison
79  integer,dimension(nbregion) :: inp ! surface posee
80  integer,dimension(nbregion) :: inf ! surface flottante
81  real,dimension(nbregion) :: isacc ! acc moy sur calotte posee
82  real,dimension(nbregion) :: isabl ! abl moy sur calotte posee
83  real,dimension(nbregion) :: isablbord ! abl sur les bords calotte
84  real,dimension(nbregion) :: ablatot ! abl totale : abl + ablbord
85  real,dimension(nbregion) :: iscalv ! calving
86  real,dimension(nbregion) :: isbm ! isacc + isabl + iscalv + isablbord
87  real,dimension(nbregion) :: Tjulytot ! total Tjuly sur calotte
88  real,dimension(nbregion) :: Tjulymean ! moy Tjuly sur calotte posee
89  real,dimension(nbregion) :: Hmean ! Epaisseur moyenne calotte posee
90  real,dimension(nbregion) :: Hmax ! Epaisseur max calotte posee
91  integer,dimension(nbregion) :: nabl ! nbr points zone d'ablation
92  integer,dimension(nbregion) :: nacc ! nbr points zone d'accumulation
93  real,dimension(nbregion) :: Tacc ! acc sur zone englacee (glace pose + shelf)
94  real,dimension(nbregion) :: Tbm ! bm total (acc+abl+calv+ablbord) sur zone englacee (glace pose + shelf)
95
96  integer :: kk
97
98  DO kk = 1,nbregion
99     INP(kk) = 0
100     INF(kk) = 0
101     isvol(kk) = 0.
102     isvol_shelf(kk)=0.
103     Tjulytot(kk)=0.
104     isacc(kk) = 0.
105     isabl(kk) = 0.
106     nabl(kk) = 0
107     nacc(kk) = 0
108     Tjulymean(kk) = 0.
109     Hmax(kk) = 0.
110     Tacc(kk) = 0.
111     isablbord(kk) = 0.
112     iscalv(kk) = 0.
113     ablatot(kk)= 0.
114     isbm(kk) = 0.
115     Tbm(kk) = 0.
116     isvolf(kk) = 0.
117
118
119     ! nouveau tof mai 2009
120     !        where (mask_cal(:,:,kk).and.H(:,:).gt.2..and.flot(:,:)) ISVOLF(kk) = ISVOLF(kk) + H(I,J)
121
122     INF(kk) = count(mask_cal(:,:,kk).and.(H(:,:).gt.2.).and.flot(:,:))
123     INP(kk) = count(mask_cal(:,:,kk).and.(H(:,:).gt.2.).and..not.flot(:,:))
124     isvol(kk) = sum(H(:,:),mask=(mask_cal(:,:,kk).and.(H(:,:).gt.2.).and..not.flot(:,:)))
125     isvol_shelf(kk) = sum(H(:,:),mask=(mask_cal(:,:,kk).and.(H(:,:).gt.2.).and.flot(:,:)))
126     Tjulytot(kk) = sum(Tjuly(:,:),mask=(mask_cal(:,:,kk).and.(H(:,:).gt.2.).and..not.flot(:,:)))
127     isacc(kk) = sum(Acc(:,:),mask=(mask_cal(:,:,kk).and.(H(:,:).gt.2.).and..not.flot(:,:)))
128     isabl(kk) = sum(Abl(:,:),mask=(mask_cal(:,:,kk).and.(H(:,:).gt.2.).and..not.flot(:,:)))
129     nabl(kk) = count(mask_cal(:,:,kk).and.(H(:,:).gt.2.).and..not.flot(:,:).and.BM(:,:).LT.0.)
130     nacc(kk) = count(mask_cal(:,:,kk).and.(H(:,:).gt.2.).and..not.flot(:,:).and.BM(:,:).GT.0.)
131     Tjulymean(kk) = sum(Tjuly(:,:),mask=(mask_cal(:,:,kk).and.(H(:,:).gt.2.).and..not.flot(:,:)))
132     Hmax(kk) = maxval(H(:,:),mask=(mask_cal(:,:,kk).and.(H(:,:).gt.2.).and..not.flot(:,:)))
133     Tacc(kk) = sum(Acc(:,:),mask=(mask_cal(:,:,kk).and.(H(:,:).gt.2.)))
134     isablbord(kk) = sum(ablbord(:,:),mask=(mask_cal(:,:,kk)))
135     iscalv(kk) =  sum(calv(:,:),mask=(mask_cal(:,:,kk).and.(H(:,:).gt.2.)))/dt
136
137     ablatot(kk) = isabl(kk) + isablbord(kk)
138     isbm(kk) = isacc(kk)+isabl(kk)+iscalv(kk)+isablbord(kk)
139     Tbm(kk) = Tacc(kk)+isabl(kk)+iscalv(kk)+isablbord(kk)
140
141     do j=1,ny
142        do i=1,nx
143           if (mask_cal(i,j,k).and..not.flot(i,j).and.H(i,j).GT.1..and.((sealevel-B(i,j)).LE.0.)) then
144              isvolf(kk) = isvolf(kk) + H(i,j)
145           else
146              isvolf(kk) = isvolf(kk) + H(i,j)-row/ro*(sealevel-B(i,j))
147           endif
148        enddo
149     enddo
150
151
152
153     ! == Les moyennes     
154     IF(INP(KK).ne.0)THEN
155        Hmean(KK) = isvol(KK) / INP(KK)
156        Tjulymean(KK)   = Tjulytot(KK) / INP(KK)
157     ENDIF
158     ! == Les volmes intergrées (3D)
159     isvol(kk) = isvol(kk)*dx*dy     
160     isacc(kk)=isacc(kk)*dx*dy
161     isabl(kk)=isabl(kk)*dx*dy
162     isablbord(kk)=isablbord(kk)*dx*dy
163     ablatot(kk)=ablatot(kk)*dx*dy
164     iscalv(kk)=iscalv(kk)*dx*dy
165     isbm(kk)=isbm(kk)*dx*dy
166     tacc(kk)=tacc(kk)*dx*dy
167     tbm(kk)=tbm(kk)*dx*dy
168  enddo
169 
170       
171 
172
173!  write(num_ritz,905)   time,((isvol(kk),inp(kk),isvolf(kk),isvol_shelf(kk),inf(kk),isacc(kk),isabl(kk),    & 
174!       isablbord(kk),ablatot(kk),iscalv(kk),isbm(kk),Tjulymean(kk),Hmean(kk),Hmax(kk),nabl(kk),nacc(kk)),kk=1,nbregion)
175
176  write(num_ritz,906) time,diff_H,water_bilan,sum(calv_dtt(2:nx-1,2:ny-1))/dtt, &
177                         sum(ablbord_dtt(2:nx-1,2:ny-1))/dtt, &
178                         sum(Bm_dtt(2:nx-1,2:ny-1))/dtt,sum(bmelt_dtt(2:nx-1,2:ny-1))/dtt,sum(ice(2:nx-1,2:ny-1),mask=ice(2:nx-1,2:ny-1)==1) 
179
180905  format(f10.1,1x,2(e11.4, 1x, i5, 1x, e11.4, 1x, e11.4, 1x, i5, 9(1x, e12.5),2(1x,i5)))
181906  format (f0.2,6(1x,e15.8),1x,i7)
182         
183! pour verifier la zone groenland sur carte
184!  where (mask_cal(:,:,2))
185!     Tann(:,:)=40.
186!  endwhere
187 
188
189end subroutine shortoutput
190end module  output_greeneem_mod
Note: See TracBrowser for help on using the repository browser.