source: branches/iLoveclim/SOURCES/bmelt_clio_coupl_mod.f90 @ 254

Last change on this file since 254 was 244, checked in by aquiquet, 5 years ago

Grisli-iloveclim branch merged to trunk at revision 243

File size: 6.8 KB
Line 
1!> \file bmelt_clio_coupl_mod.f90
2!! Read the bmelt computed in CLIO (thersf.f) for the 20 vertical layers
3!<
4
5!> \namespace  BMELT_CLIO_COUPL_MOD
6!! Read the bmelt computed in CLIO and compute grounded basal melt
7!! @note Only for coupled version
8!! \author Aurelien Quiquet
9!! \date October 2016
10!! @note Used module
11!! @note   - use module3D_phy
12!<
13
14
15MODULE  BMELT_CLIO_COUPL_MOD
16
17
18  USE module3D_phy,only:nx,ny,i,j,ro,row,h,bsoc,hdot,bmelt,corrbmelt,igrdline,flot,fbm,bmshelfCLIO
19
20implicit none
21
22real, parameter       :: bmgrz_fact = 2. !< bmshelf/bmgrz ratio (fixed)
23
24REAL,dimension(nx,ny) ::  bmgrz     !< fusion basale a la grounding zone
25real,dimension(nx,ny) ::  bmshelf   !< fusion basale sous shelf
26
27real,dimension(20)    ::  z_CLIO    !< depth of the CLIO layers (center of layer)
28real,dimension(20)    ::  dz_CLIO   !< thickness of the CLIO layers
29
30
31CONTAINS
32!-------------------------------------------------------------------------------
33
34!> SUBROUTINE: init_bmelt
35!! This routine does the initialisation of basal melting rates of ice shelves
36!<
37subroutine init_bmelt
38
39! local variables:
40integer :: locdepth ! local depth of the shelf
41integer :: noc      ! loop integer on the vertical oceanic layers
42
43! This routine does the initialisation of basal melting rates of ice shelves
44!  -  z_CLIO
45!  - dz_CLIO
46!  - bmshelf and bmgrz
47! Called by initial-0.3.f90
48
49!    ecriture dans le fichier parametres
50     write(42,*)'fusion basale sous les ice shelves : bmelt from CLIO   '
51     write(42,*)'-------------------------------------------------------'
52
53!the depths of the centers of CLIO vertical layers:
54     z_CLIO(20)  = 5.00
55     z_CLIO(19)  = 15.98
56     z_CLIO(18)  = 29.17
57     z_CLIO(17)  = 45.20
58     z_CLIO(16)  = 64.96
59     z_CLIO(15)  = 89.75
60     z_CLIO(14)  = 121.52
61     z_CLIO(13)  = 163.28
62     z_CLIO(12)  = 219.86
63     z_CLIO(11)  = 299.26
64     z_CLIO(10)  = 415.07
65     z_CLIO(9)   = 588.88
66     z_CLIO(8)   = 850.19
67     z_CLIO(7)   = 1225.11
68     z_CLIO(6)   = 1717.90
69     z_CLIO(5)   = 2307.36
70     z_CLIO(4)   = 2963.25
71     z_CLIO(3)   = 3661.11
72     z_CLIO(2)   = 4385.22
73     z_CLIO(1)   = 5126.18
74     
75!the thicknesses of the CLIO vertical layers:
76     dz_CLIO(20) = 10.00
77     dz_CLIO(19) = 11.96
78     dz_CLIO(18) = 14.42
79     dz_CLIO(17) = 17.64
80     dz_CLIO(16) = 21.88
81     dz_CLIO(15) = 27.70
82     dz_CLIO(14) = 35.84
83     dz_CLIO(13) = 47.68
84     dz_CLIO(12) = 65.48
85     dz_CLIO(11) = 93.38
86     dz_CLIO(10) = 138.18
87     dz_CLIO(9)  = 209.44
88     dz_CLIO(8)  = 313.18
89     dz_CLIO(7)  = 436.66
90     dz_CLIO(6)  = 548.92
91     dz_CLIO(5)  = 630.00
92     dz_CLIO(4)  = 681.78
93     dz_CLIO(3)  = 713.94
94     dz_CLIO(2)  = 734.28
95     dz_CLIO(1)  = 747.64
96
97     
98     do j=1,ny
99        do i=1,nx
100
101! Init: everywhere to surface CLIO melt.
102! In CLIO, when we don't have ocean, I assumed a very high bm
103!          In this case, in GRISLI, we put constant values (0.2)
104           if (bmshelfCLIO(i,j,20).lt.99d0) then!
105              bmshelf(i,j) = real(bmshelfCLIO(i,j,20))
106              bmgrz(i,j) = bmshelf(i,j) * bmgrz_fact
107           else
108              bmshelf(i,j) = 0.2
109              bmgrz(i,j) = bmshelf(i,j) * bmgrz_fact
110           endif
111
112           if(Bsoc(i,j).lt.-1500) then ! the melt is higher above deep ocean
113              bmshelf(i,j) = 20. !bmshelf(i,j) * 10.
114              bmgrz(i,j) =   20. !bmgrz(i,j)   * 10.
115           endif
116
117! Now, we look at the depth of the ice shelves to use the right bm
118           !if (flot(i,j).and.(H(i,j).gt.1.)) then
119           if (flot(i,j)) then
120             
121              bmelt(i,j) = bmshelf(i,j) ! init
122             
123              locdepth=ro/row*H(i,j)
124              do noc=20,2,-1
125                 if ( locdepth .gt. z_CLIO(noc)+dz_CLIO(noc)/2. ) then
126                    if (bmshelfCLIO(i,j,noc-1).lt.99d0) then
127                       bmelt(i,j) = real(bmshelfCLIO(i,j,noc-1))
128                    endif
129                 else
130                    exit
131                 endif
132              enddo
133             
134           endif
135           
136        enddo
137     enddo
138
139
140      return
141      end subroutine init_bmelt
142
143!________________________________________________________________________________
144
145!> SUBROUTINE: bmeltshelf
146!! This routine computes the actual basal melting rates
147!<
148subroutine bmeltshelf
149
150! local variables:
151integer :: locdepth ! local depth of the shelf
152integer :: noc      ! loop integer on the vertical oceanic layers
153integer :: ngr      ! number of floating points, neighbours of a grounded points
154real    :: bmsum    ! temporary bm
155
156do j=1,ny
157   do i=1,nx
158
159! Init: everywhere to surface CLIO melt.
160! In CLIO, when we don't have ocean, I assumed a very high bm
161!          In this case, in GRISLI, we put constant values (0.2)
162      if (bmshelfCLIO(i,j,20).lt.99d0) then!
163         bmshelf(i,j) = real(bmshelfCLIO(i,j,20))
164         bmgrz(i,j) = bmshelf(i,j) * bmgrz_fact
165      else
166         bmshelf(i,j) = 0.2
167         bmgrz(i,j) = bmshelf(i,j) * bmgrz_fact
168      endif
169
170      if(Bsoc(i,j).lt.-1500) then ! the melt is higher above deep ocean
171         bmshelf(i,j) = 20. !bmshelf(i,j) * 10.
172         bmgrz(i,j) =   20. !bmgrz(i,j)   * 10.
173      endif
174
175! Now, we look at the depth of the ice shelves to use the right bm
176      if (flot(i,j)) then    ! partie flottante
177
178         bmelt(i,j) = bmshelf(i,j) ! init
179         
180         locdepth=ro/row*H(i,j)
181         do noc=20,2,-1
182            if ( locdepth.gt. z_CLIO(noc)+dz_CLIO(noc)/2. ) then
183               if (bmshelfCLIO(i,j,noc-1).lt.99d0) then
184                  bmelt(i,j) = real(bmshelfCLIO(i,j,noc-1))
185               endif
186            else
187               exit
188            endif
189         enddo
190         
191         if (fbm(i,j))  bmelt(i,j)=bmgrz(i,j)
192
193
194! ATTENTION LE BLOC SUIVANT SERT A FAIRE DES ICE SHELVES STATIONNAIRES
195! igrdline est défini dans itnitial1
196! afq -- not tested for coupled applications...
197         if (igrdline.eq.1) then
198            corrbmelt(i,j)=corrbmelt(i,j)+hdot(i,j)*0.8
199            bmelt(i,j)=bmelt(i,j)+corrbmelt(i,j)
200         endif
201
202      endif ! on flot
203   enddo
204enddo
205
206do j=2,ny-1
207   do i=2,nx-1
208     
209      if (.not.flot(i,j)) then   ! grounded point, we account for the floating neighbours
210
211         bmsum=0.
212         ngr=0
213         if (flot(i+1,j)) then
214            ngr=ngr+1
215            bmsum= bmsum+bmelt(i+1,j)
216         endif
217         if (flot(i-1,j)) then
218            ngr=ngr+1
219            bmsum= bmsum+bmelt(i-1,j)
220         endif
221         if (flot(i,j+1)) then
222            ngr=ngr+1
223            bmsum= bmsum+bmelt(i,j+1)
224         endif
225         if (flot(i,j-1)) then
226            ngr=ngr+1
227            bmsum= bmsum+bmelt(i,j-1)
228         endif
229
230! Grounding point basal melting rate is a combined effect of grounded and floating values:
231
232           bmelt(i,j)= ngr/4.*bmgrz(i,j)+(1.-ngr/4.)*bmsum
233
234        endif
235
236     end do
237  end do
238
239
240    return
241    end subroutine  bmeltshelf
242
243
244
245END MODULE  BMELT_CLIO_COUPL_MOD
Note: See TracBrowser for help on using the repository browser.