source: trunk/SOURCES/Ant40_files/output_anta40_mod-0.4.f90 @ 144

Last change on this file since 144 was 144, checked in by aquiquet, 7 years ago

Series of minor bug corrections for initMIP Antarctica configuration

File size: 10.4 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
16use bilan_eau_mod
17use netcdf
18use io_netcdf_grisli
19use bilan_flux_mod
20
21implicit none
22     
23!real ::  vol ; !integer :: np
24integer :: nflot                      !< nbr de point flottant
25real ::  bmean                        !<
26real ::  accmean                      !< accumulation moyenne
27real ::  ablmean                      !< ablation moyenne
28real ::  calvmean                     !< moyenne calving
29real ::  ablbordmean                  !<
30real ::  bmeltmean                    !< moyenne fusion basale
31real ::  tbmean                       !< temperature basale moyenne
32real ::  tbdotmean                    !< moyenne variation / temps temperature basale
33real ::  vsmean                       !< vitesse de surface moyenne
34!real ::  vsdotmean                    !< moyenne variation / temps vitesse de surface
35!real ::  uzsmean   !!!! utilise ?     !< vitesse verticale de surface moyenne
36real ::  uzsdotmean                   !< moyenne variation / temps vitesse verticale de surface
37real ::  uzkmean                      !< moyenne vitesse verticale de surface
38real ::  hdotmean                     !< moyenne derivee / temps de h
39real ::  bdotmean                     !< moyenne bedrock derive / temps
40real ::  volf                         !< volume au dessus de la flottaison
41
42real :: lim                           !< Total ice mass
43real :: iareag                        !< surface posee
44real :: iareaf                        !< surface flottante
45real :: tendacabf                     !< Total SMB flux
46real :: tendlibmassbf                 !< Total Basal mass balance flux
47real :: tendlicalvf                   !< Total calving flux
48real :: tendligroundf                 !< Total grounding line flux
49
50real,dimension(nx,ny) :: corrsurf     !< facteur de correction de la surface
51!real,parameter :: ice_density=910.    !< densite de la glace pour conversion en masse
52
53! variables netcdf
54integer,parameter :: ncshortout=1 ! 1 sorties netcdf short initMIP
55integer,parameter :: nvar=8 ! nombre de variables dans le fichier de sortie temporel netcdf
56integer :: ncid
57integer :: status
58integer :: timeDimID
59integer :: timeVarID
60integer,dimension(nvar) :: varID
61integer :: nbtimeout  ! index time output
62
63real,dimension(nvar) :: var_shortoutput
64
65
66CONTAINS
67
68subroutine init_outshort
69
70double precision,dimension(:,:),pointer      :: tab               !< tableau 2d real pointer
71character(len=100),dimension(nvar) :: namevar ! name, standard_name, long_name, units
72character(len=100),dimension(nvar) :: standard_name
73character(len=100),dimension(nvar) :: long_name
74character(len=100),dimension(nvar) :: units
75
76!ndisp sorite courte tous les ndisp
77NDISP=100
78
79
80
81if (ncshortout.eq.1) then  ! ecriture netcdf
82
83! lecture du fichier avec les corrections de surface
84  call Read_Ncdf_var('z',trim(DIRNAMEINP)//'/corrsurf-initMIP-16km.grd',tab)
85  corrsurf(:,:)=tab(:,:)
86
87  open(568,file=trim(dirsource)//'/Fichiers-parametres/short-initMIPnc.dat',status='old')
88! lecture en-tete
89  read(568,*)
90  read(568,*)
91  read(568,*)
92  read(568,*)
93  read(568,*)
94! lecture des infos sur les variables :
95  do k=1,nvar
96    read(568,'(a100)') namevar(k)
97    read(568,'(a100)') standard_name(k)
98    read(568,'(a100)') long_name(k)
99    read(568,'(a100)') units(k)
100    read(568,*)
101  enddo
102  close(568)
103! Fichier Netcdf initMIP
104! creation du fichier Netcdf :
105  status=nf90_create(path = 'short'//runname//'.nc', cmode = nf90_clobber, ncid = ncid)
106  if (status /= nf90_noerr) call handle_err(status)
107
108! definition des dimension :
109  status=nf90_def_dim(ncid, name="time", len=NF90_UNLIMITED, dimid=timeDimID)
110  if (status /= nf90_noerr) call handle_err(status)
111  status=nf90_def_var(ncid, name="time", xtype=nf90_float, dimids=(/ timeDimID/), varid=timeVarID) 
112  if (status /= nf90_noerr) call handle_err(status)
113  status=nf90_put_att(ncid, timeVarID, "standard_name", "time")
114  if (status /= nf90_noerr) call handle_err(status)
115  status=nf90_put_att(ncid, timeVarID,"units", "years since 2007-01-01 00:00:00")
116  if (status /= nf90_noerr) call handle_err(status)
117
118! definition des variables de sortie :
119  do k=1,nvar  ! boucle sur le nbr de variable a definir
120    status=nf90_def_var(ncid, name=trim(namevar(k)), xtype=nf90_float, dimids= &
121          (/ timeDimID /), varid=varID(k))
122    if (status /= nf90_noerr) call handle_err(status)
123    status=nf90_put_att(ncid, varID(k), "standard_name", trim(standard_name(k)))
124    if (status /= nf90_noerr) call handle_err(status)
125    status=nf90_put_att(ncid, varID(k), "long_name", trim(long_name(k)))
126    if (status /= nf90_noerr) call handle_err(status)
127    status=nf90_put_att(ncid, varID(k), "units", trim(units(k)))
128    if (status /= nf90_noerr) call handle_err(status)
129  enddo
130
131! fin de la definition du fchier :
132  status=nf90_enddef(ncid)
133  if (status /= nf90_noerr) call handle_err(status)
134  nbtimeout = 0 ! initialisation compteur sorties axe time
135else ! pas de sortie netcdf et sans correction de surface
136  corrsurf(:,:)=1.
137endif
138
139end subroutine init_outshort
140
141
142
143!_________________________________________________________________________
144subroutine shortoutput
145
146! 1_initialization
147!------------------
148real ::  smax
149
150      vol=0. 
151      np=0
152      nflot=0
153      hmax=0. 
154      smax=0.
155      bmean=0. 
156      accmean=0. 
157      ablmean=0. 
158      calvmean=0. 
159      ablbordmean=0.
160      bmeltmean=0.
161      tbmean=0.
162      tbdotmean=0.
163      vsmean=0.
164!      vsdotmean=0.
165!      uzsmean=0.
166      uzsdotmean=0.
167      uzkmean=0.
168      hdotmean=0.
169      bdotmean=0.
170      volf=0.
171      lim=0.
172      tendacabf=0.
173      iareag=0.
174      iareaf=0.
175      tendlicalvf=0.
176      tendligroundf=0.
177      tendlibmassbf=0.
178! 2_preparing outputs
179!--------------------     
180    do j=1,ny
181      do i=1,nx
182        if (ice(i,j).eq.1) then ! point englace
183          if (.not.flot(i,j)) then ! point pose
184            np=np+1
185            vol=vol+h(i,j)
186            iareag=iareag+1.*corrsurf(i,j)                            ! surface englacee posee
187
188!         calcul de la hauteur au dessus de la flottaison
189            if (sealevel-B(i,j).le.0.) then    ! socle au dessus du niveau des mers
190              volf=volf+h(i,j)*corrsurf(i,j)                          ! volume au-dessus de la flottaison
191            else
192              volf=volf+(h(i,j)-row/ro*(sealevel-b(i,j)))*corrsurf(i,j) ! volume au-dessus de la flottaison
193            endif
194
195            if (h(i,j).gt.hmax) hmax=h(i,j) 
196            if (s(i,j).gt.smax) smax=s(i,j) 
197            bmean=bm(i,j)+bmean 
198            accmean=acc(i,j)+accmean
199            tbmean=tbmean+t(i,j,nz)
200            tbdotmean=tbdotmean+tbdot(i,j)
201            vsmean=vsmean+sqrt(ux(i,j,1)**2+uy(i,j,1)**2)
202!          vsdotmean=vsdotmean+vsdot(i,j)
203!          uzsmean=uzsmean+uz(i,j,1)
204            uzsdotmean=uzsdotmean+uzsdot(i,j)
205            uzkmean=uzkmean+uzk(i,j)
206            hdotmean=hdotmean+abs(hdot(i,j)) 
207            bdotmean=bdotmean+abs(bdot(i,j)) 
208            bmeltmean=bmeltmean+bmelt(i,j)
209          else ! point flottant
210            iareaf=iareaf+1.*corrsurf(i,j)                               ! surface flottante
211          endif
212          lim=lim+h(i,j)*corrsurf(i,j)                                   ! volume total de glace
213          tendacabf=tendacabf+bm_dtt(i,j)*corrsurf(i,j)/dtt              ! smb surface
214          tendlibmassbf=tendlibmassbf-bmelt_dtt(i,j)*corrsurf(i,j)/dtt   ! fonte basale     
215        endif
216        tendlicalvf=tendlicalvf+calv_dtt(i,j)*corrsurf(i,j)/dtt        ! calving
217        tendlibmassbf=tendlibmassbf-ablbord_dtt(i,j)*corrsurf(i,j)/dtt ! partie ablbord de la fonte basale
218        tendligroundf=tendligroundf+grline_dtt(i,j)*corrsurf(i,j)/dtt  ! flux a la grounding line
219      end do
220    end do
221
222
223      if (np.ne.0) then
224        hmean=vol/np 
225        vol=vol*dx*dy 
226        volf=volf*dx*dy*ice_density
227        bmean=bmean/np 
228        accmean=accmean/np 
229        ablmean=bmean-accmean 
230        calvmean=calvmean/np 
231        bmeltmean=bmeltmean/np
232        ablbordmean=ablbordmean/np
233        tbmean=tbmean/np
234        tbdotmean=tbdotmean/np
235        vsmean=vsmean/np
236!        vsdotmean=vsdotmean/np
237!        uzsmean=uzsmean/np
238        uzsdotmean=uzsdotmean/np
239        uzkmean=uzkmean/np
240        hdotmean=hdotmean/np
241      endif
242      lim=lim*dx*dy*ice_density
243      iareag=iareag*dx*dy 
244      iareaf=iareaf*dx*dy
245      tendacabf=tendacabf*dx*dy*ice_density/secyear
246      tendlibmassbf=tendlibmassbf*dx*dy*ice_density/secyear
247      tendlicalvf=tendlicalvf*dx*dy*ice_density/secyear
248      tendligroundf=tendligroundf*ice_density/secyear
249     
250     
251      bdotmean=bdotmean/nx/ny 
252
253
254! 2_writing outputs
255!------------------   
256!     **** short display ****
257
258        write(num_ritz,904) nt,time,tafor,sealevel,vol,volf,np, &
259          nint(hmean),nint(smax),                    &
260          bmean,tbmean,nint(vsmean),                 &
261                                  tbdotmean,hdotmean,dt,accmean, &
262                                  diff_H,water_bilan,sum(calv_dtt(:,:))/dtt, &
263                                  sum(ablbord_dtt(:,:))/dtt, &
264                                  sum(Bm_dtt(:,:))/dtt,sum(bmelt_dtt(:,:))/dtt
265
266
267903   format(i8,1x,f0.2,1x,f0.4,1x,f0.2,1x,2(e10.5,1x),i6,1x,i4,1x,i5,1x, &
268             f0.4,1x,f0.3,1x,i3,4(1x,e8.2),1x,f0.4,1x,f0.4) 
269904   format(i8,1x,f0.2,4(1x,e15.8),3(1x,i8),2(1x,e15.8),1x,i8,10(1x,e15.8))
270!940   format('%%%% ',a,'   time=',f8.0,' %%%%')
271
272
273if (ncshortout.eq.1) then  ! ecriture netcdf
274  ! Total ice mass
275  var_shortoutput(1)=lim
276  ! Mass above floatation
277  var_shortoutput(2)=volf
278  ! Grounded ice area
279  var_shortoutput(3)=iareag
280  ! Floating ice area
281  var_shortoutput(4)=iareaf
282  ! Total SMB flux
283  var_shortoutput(5)=tendacabf
284  ! Total Basal mass balance flux
285  var_shortoutput(6)=tendlibmassbf
286  ! Total calving flux
287  var_shortoutput(7)=tendlicalvf
288  ! Total grounding line flux
289  var_shortoutput(8)=tendligroundf
290
291  nbtimeout=nbtimeout+1
292 
293  status=nf90_put_var(ncid, timeVarID, time, start=(/nbtimeout/))
294  if (status /= nf90_noerr) call handle_err(status)
295
296  do k=1,nvar  ! boucle sur le nbr de variable a ecrire
297    status=nf90_put_var(ncid, varID(k), var_shortoutput(k),start=(/nbtimeout/))
298    if (status /= nf90_noerr) call handle_err(status)
299  enddo
300  status=nf90_sync(ncid)
301  if (status /= nf90_noerr) call handle_err(status)
302endif
303
304
305end subroutine shortoutput
306
307subroutine handle_err(status)
308  integer, intent(in) :: status
309  if (status /= nf90_noerr) then
310     print*,trim(nf90_strerror(status))
311     stop "stopped"
312  end if
313end subroutine handle_err
314
315end module  output_antarcti_mod
Note: See TracBrowser for help on using the repository browser.