!> \file output_anta_mod-0.4.f90 !! Module de !< !> \namespace output_antarcti_mod !! Module de !! \author ... !! \date ... !! @note Used module !! @note - use module3D_phy !< module output_antarcti_mod USE module3D_phy implicit none !real :: vol ; !integer :: np real :: bmean !< real :: accmean !< accumulation moyenne real :: ablmean !< ablation moyenne real :: calvmean !< moyenne calving real :: ablbordmean !< real :: bmeltmean !< moyenne fusion basale real :: tbmean !< temperature basale moyenne real :: tbdotmean !< moyenne variation / temps temperature basale real :: vsmean !< vitesse de surface moyenne !real :: vsdotmean !< moyenne variation / temps vitesse de surface !real :: uzsmean !!!! utilise ? !< vitesse verticale de surface moyenne real :: uzsdotmean !< moyenne variation / temps vitesse verticale de surface real :: uzkmean !< moyenne vitesse verticale de surface real :: hdotmean !< moyenne derivee / temps de h real :: bdotmean !< moyenne bedrock derive / temps real :: volf !< volume au dessus de la flottaison CONTAINS subroutine init_outshort !ndisp sorite courte tous les ndisp NDISP=100 end subroutine init_outshort !_________________________________________________________________________ subroutine shortoutput ! 1_initialization !------------------ real :: smax vol=0. np=0 hmax=0. smax=0. bmean=0. accmean=0. ablmean=0. calvmean=0. ablbordmean=0. bmeltmean=0. tbmean=0. tbdotmean=0. vsmean=0. ! vsdotmean=0. ! uzsmean=0. uzsdotmean=0. uzkmean=0. hdotmean=0. bdotmean=0. volf=0. ! 2_preparing outputs !-------------------- do i=1,nx do j=1,ny if (.not.flot(i,j)) then ! if (h(i,j).gt.1.) then np=np+1 vol=vol+h(i,j) ! calcul de la hauteur au dessus de la flottaison if (sealevel-B(i,j).le.0.) then ! socle au dessus du niveau des mers volf=volf+h(i,j) else volf=volf+h(i,j)-row/ro*(sealevel-b(i,j)) endif if (h(i,j).gt.hmax) hmax=h(i,j) if (s(i,j).gt.smax) smax=s(i,j) bmean=bm(i,j)+bmean accmean=acc(i,j)+accmean tbmean=tbmean+t(i,j,nz) tbdotmean=tbdotmean+tbdot(i,j) vsmean=vsmean+sqrt(ux(i,j,1)**2+uy(i,j,1)**2) ! vsdotmean=vsdotmean+vsdot(i,j) ! uzsmean=uzsmean+uz(i,j,1) uzsdotmean=uzsdotmean+uzsdot(i,j) uzkmean=uzkmean+uzk(i,j) hdotmean=hdotmean+abs(hdot(i,j)) bdotmean=bdotmean+abs(bdot(i,j)) bmeltmean=bmeltmean+bmelt(i,j) endif calvmean=calvmean+calv(i,j) ablbordmean=ablbordmean+ablbord(i,j) end do end do if (np.ne.0) then hmean=vol/np vol=vol*dx*dy volf=volf*dx*dy bmean=bmean/np accmean=accmean/np ablmean=bmean-accmean calvmean=calvmean/np bmeltmean=bmeltmean/np ablbordmean=ablbordmean/np tbmean=tbmean/np tbdotmean=tbdotmean/np vsmean=vsmean/np ! vsdotmean=vsdotmean/np ! uzsmean=uzsmean/np uzsdotmean=uzsdotmean/np uzkmean=uzkmean/np hdotmean=hdotmean/np endif bdotmean=bdotmean/nx/ny ! 2_writing outputs !------------------ ! **** short display **** write(num_ritz,903) nt,time,tafor,sealevel,vol,volf,np, & nint(hmean),nint(smax), & bmean,tbmean,nint(vsmean), & ! tbdotmean,vsdotmean,hdotmean,bdotmean, & ! tbdotmean,hdotmean,dt,bmeltmean,accmean tbdotmean,hdotmean,dt,bmelt(3,3),accmean 903 format(i8,1x,f0.2,1x,f0.4,1x,f0.2,1x,2(e10.5,1x),i6,1x,i4,1x,i5,1x, & f0.4,1x,f0.3,1x,i3,4(1x,e8.2),1x,f0.4,1x,f0.4) !940 format('%%%% ',a,' time=',f8.0,' %%%%') end subroutine shortoutput end module output_antarcti_mod