source: LMDZ6/branches/Amaury_dev/libf/phylmd/inlandsis/sisvat_bsn.f90

Last change on this file was 5117, checked in by abarral, 2 months ago

rename modules properly lmdz_*
move some unused files to obsolete/
(lint) uppercase fortran keywords

File size: 3.4 KB
Line 
1
2
3SUBROUTINE SISVAT_BSn
4
5  ! +------------------------------------------------------------------------+
6  ! | MAR          SISVAT_BSn                               04-apr-2020  MAR |
7  ! |   SubRoutine SISVAT_BSn treats Snow Erosion                            |
8  ! |   (not deposition anymore since 2-jun 2018)                            |
9  ! |                                                                        |
10  ! |   SISVAT_bsn computes the snow erosion mass according to both the      |
11  ! |   theoretical maximum erosion amount computed in inlandsis and the     |
12  ! |   availability of snow (currently in the uppermost snow layer only)    |
13  ! |                                                                        |
14  ! +------------------------------------------------------------------------+
15
16
17
18
19  ! +--General Variables
20  ! +  =================
21
22  USE VARphy
23  USE VAR_SV
24  USE VARdSV
25  USE VARxSV
26  USE VARySV
27
28
29   IMPLICIT NONE
30
31  ! +--Local Variables
32  ! +  ===============
33
34
35  INTEGER :: ikl   ,isn
36  REAL :: h_mmWE                        ! Eroded Snow Layer Min Thickness
37  REAL :: dbsaux(knonv)                 ! Drift Amount   (Dummy Variable)
38  REAL :: dzweqo,dzweqn,bsno_x          ! Conversion variables for erosion
39  REAL :: dz_new,rho_new
40  REAL :: snofOK                        ! Threshd Snow Fall
41  REAL :: Fac                           ! Correction factor for erosion
42  REAL :: densif                        ! Densification rate if erosion
43
44  ! +--DATA
45  ! +  ====
46
47  data     h_mmWE  / 0.01e00  /          ! Eroded Snow Layer Min Thickness
48
49  ! +--EROSION
50  ! +  =======
51
52  !DO isn = nsno,2,-1
53  DO ikl = 1,knonv
54
55    isn         = isnoSV(ikl)
56    dzweqo      = dzsnSV(ikl,isn) *ro__SV(ikl,isn)      ! [kg/m2, mm w.e.]
57
58    bsno_x      = min(0.,dbs_SV(ikl))
59    ! Fac         = min(1.,max(1-(ro__SV(ikl,isn)/700.),0.)**2)
60    ! Fac         = min(1.,max(1-(qsnoSV(ikl)*1000/30.),0.))
61    ! bsno_x      = bsno_x*Fac
62
63    dzweqn      = dzweqo + bsno_x
64    dzweqn      = max(dzweqn,h_mmWE)
65    dzweqn      = min(dzweqn,dzweqo)
66  !XF
67    dbs_SV(ikl) = dbs_SV(ikl)    +(dzweqo -dzweqn)
68    dbs_Er(ikl) = dbs_Er(ikl)    +(dzweqo -dzweqn)
69    dzsnSV(ikl,isn) =              dzweqn &
70          /max(epsi,ro__SV(ikl,isn))
71
72    ! Densification of the uppermost snow layer if erosion:
73    IF((dzweqo-dzweqn)>0                    .AND. &
74          dzsnSV(ikl,isn)>0                    .AND. &
75          ro__SV(ikl,max(1,isnoSV(ikl)))<roBdSV) THEN
76    !characteristic time scale for drifting snow compaction set to 24h
77    !linear densification rate [kg/m3/s] over 24h
78    densif         = (450. - frsno) / (3600*24)
79
80    !Attenuation of compaction rate from 450 to 500 kg/m3
81    Fac         = 1-((ro__SV(ikl,max(1,isnoSV(ikl))) &
82          -roBdSV)/(500.-roBdSV))
83    Fac         = max(0.,min(1.,Fac))
84
85    IF (ro__SV(ikl,max(1,isnoSV(ikl)))>roBdSV) THEN
86      densif=densif*Fac
87    endif
88
89    rho_new        = min(roBdSV,ro__SV(ikl,isn)+densif*dt__SV)
90    dz_new         = dzsnSV(ikl,isn)*ro__SV(ikl,isn)/rho_new
91    ro__SV(ikl,isn)=rho_new
92    dzsnSV(ikl,isn)=dz_new
93    endif
94
95    IF(dzsnSV(ikl,isn)>0 .AND.dzsnSV(ikl,isn)<0.0001)THEN
96    dbs_SV(ikl) = dbs_SV(ikl)+ dzsnSV(ikl,isn)*ro__SV(ikl,isn)
97    dbs_Er(ikl) = dbs_Er(ikl)+ dzsnSV(ikl,isn)*ro__SV(ikl,isn)
98    dzsnSV(ikl,isn) = 0
99    ro__SV(ikl,isn) = 0
100    isnoSV(ikl)     = max(0,isnoSV(ikl) - 1)
101    endif
102
103  END DO
104  !END DO
105
106
107END SUBROUTINE SISVAT_BSn
Note: See TracBrowser for help on using the repository browser.