source: trunk/SOURCES/bilan_flux_output_mod.f90 @ 137

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

Add bilan_flux_output and secyear in output_anta40_mod

File size: 3.2 KB
Line 
1!> \file bilan_flux_output_mod.f90
2!! Clacul du bilan des flux : sorties initMIP
3!<
4     
5
6!> MODULE: bilan_flux
7!! Calcule le bilan des flux : sortie initMIP
8!! \author C. Dumas
9!! \date 10/10/2017
10!! @note Calcul des flux output initMIP
11!>
12
13module bilan_flux_mod
14
15
16use module3D_phy
17implicit none
18
19real :: dtoutflux                       ! pas de temps des sorties flux
20real :: dtsum                           ! somme des pas de temps (pour verification)
21!real :: alpha_flot                      ! ro/row
22
23! variables flux :
24real,dimension(nx,ny) :: bm_flux        ! surface smb on ice mask
25real,dimension(nx,ny) :: bmelt_flux     ! bmelt on ice mask
26real,dimension(nx,ny) :: dhdt_flux      ! dhdt on ice mask
27real,dimension(nx,ny) :: calving_flux   ! calving on ice mask
28real,dimension(nx,ny) :: grline_flux    ! grounding line flux
29
30real,dimension(nx,ny) :: vieuxH_flux    ! H at previous time step
31!real,dimension(nx,ny) :: archimtab      ! point pose si > 0
32!integer,dimension(nx,ny) :: gr_line        ! point grounding line (pose sous niveau de la mer avec point flottant a cote)
33
34
35
36
37
38contains
39
40subroutine init_bilan_flux
41 ! initialisation des variables
42!       diff_H=0.
43!       sum_H_old = sum(H(2:nx-1,2:ny-1),mask=ice(2:nx-1,2:ny-1)==1)
44!       tot_water(:,:)=0.
45!       bm_dt(:,:)=0.
46!       bmelt_dt(:,:)=0.
47
48  dtoutflux=5. ! initMIP sorties flux tous les 5 ans
49  dtsum=0.
50  bm_flux(:,:)=0.
51  bmelt_flux(:,:)=0.
52  dhdt_flux(:,:)=0.
53  calving_flux(:,:)=0.
54  grline_flux(:,:)=0.
55 
56end subroutine init_bilan_flux
57
58       
59
60
61subroutine bilan_flux_output
62
63dtsum = dtsum + dt
64
65
66where (ice(2:nx-1,2:ny-1).eq.1)
67        bm_flux(2:nx-1,2:ny-1) = bm_flux(2:nx-1,2:ny-1) + bm(2:nx-1,2:ny-1)*dt          ! somme Bm sur dt
68        bmelt_flux(2:nx-1,2:ny-1) = bmelt_flux(2:nx-1,2:ny-1) + bmelt(2:nx-1,2:ny-1)*dt + ablbord(2:nx-1,2:ny-1)  ! somme bmelt sur dt
69  dhdt_flux(2:nx-1,2:ny-1) = dhdt_flux(2:nx-1,2:ny-1) + (H(2:nx-1,2:ny-1)-vieuxH_flux(2:nx-1,2:ny-1))*dt    ! somme dhdt  sur dt   
70endwhere
71
72calving_flux(2:nx-1,2:ny-1) = calving_flux(2:nx-1,2:ny-1) + calv(2:nx-1,2:ny-1)
73
74where (gr_line(:,:).eq.1)
75!~   grline_flux(:,:)= (((uxbar(:,:)+eoshift(uxbar(:,:),shift=1,boundary=0.,dim=1))**2+ &
76!~                     (uybar(:,:)+eoshift(uybar(:,:),shift=1,boundary=0.,dim=2))**2)**0.5)*0.5 &
77!~                     *H(:,:) + grline_flux(:,:)
78  grline_flux(:,:)= (abs(uxbar(:,:)+eoshift(uxbar(:,:),shift=1,boundary=0.,dim=1))/2.*dy + &
79                     abs(uybar(:,:)+eoshift(uybar(:,:),shift=1,boundary=0.,dim=2))/2.*dx)  &
80                    *H(:,:) + grline_flux(:,:)                     
81endwhere
82
83
84
85
86! calcul de la moyenne des flux sur dtoutflux
87if ((mod(abs(time),dtoutflux).lt.dtmin).and.(abs(dtsum-dtoutflux).lt.dtmin)) then
88  bm_flux(:,:)=bm_flux(:,:)/dtsum
89  bmelt_flux(:,:)=bmelt_flux(:,:)/dtsum
90  dhdt_flux(:,:)=dhdt_flux(:,:)/dtsum
91  calving_flux(:,:)=calving_flux(:,:)/dtsum
92  grline_flux(:,:)=grline_flux(:,:)/dtsum
93else if (abs(dtsum-dtoutflux).lt.dtmin) then
94  print*,'pb sorties flux dtoutflux : time=', time
95  print*,'dtsum=',dtsum,' dtoutflux', dtoutflux
96else if (mod(abs(time),dtoutflux).lt.dtmin) then
97  print*,'pb sorties flux dtsum : time=', time
98  print*,'dtsum=',dtsum,' dtoutflux', dtoutflux
99endif
100
101! reinitialisation des variables
102vieuxH_flux(:,:)=H(:,:)
103ablbord(:,:)=0.
104
105end subroutine bilan_flux_output
106
107end module bilan_flux_mod
Note: See TracBrowser for help on using the repository browser.