source: branches/iLoveclim/SOURCES/Hudson_files/dragging-hudson_mod.f90 @ 254

Last change on this file since 254 was 4, checked in by dumas, 10 years ago

initial import GRISLI trunk

File size: 5.3 KB
Line 
1!> \file dragging_hudson_mod.f90
2!! Module qui definie la loi de glissement dans les expériences Heino
3!<
4
5!> \namespace  dragging_hudson
6!! Definie la loi de glissement dans les expériences Heino
7!! \author ...
8!! \date ...
9!! @note Used module
10!! @note   - use module3D_phy
11!! @note   - use sedim_declar
12!<
13
14
15
16module dragging_hudson
17
18! Defini la loi de glissement dans les expériences Heino
19! modification par rapport a la version de Catherine : ice-shelves + streams autorises
20
21USE module3D_phy
22USE sedim_declar
23
24implicit none
25
26real :: Cfs                      !< coefficient glissement pour sediment
27real :: coefmax
28real :: coefslid
29real :: coefdrag
30real :: seuil_sedim              !< seuil sur hw_mx pour avoir du glissement
31real, dimension(nx,ny) :: hw_mx
32real, dimension(nx,ny) :: hw_my
33
34!character(len=80) :: filin
35
36
37contains
38
39!> SUBROUTINE: init_dragging
40!! Initialisation du dragging basal
41!<
42
43  subroutine init_dragging
44
45    implicit none
46
47! formats pour les ecritures dans 42
48428 format(A)
49
50    namelist/drag_hudson/seuil_sedim,coefmax,Cfs 
51
52! lecture des parametres du run                block drag_hudson
53!--------------------------------------------------------------------
54
55    rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
56    read(num_param,drag_hudson)
57    write(num_rep_42,428)'!___________________________________________________________' 
58    write(num_rep_42,428) '&drag_hudson                 ! nom du bloc drag_hudson'
59    write(num_rep_42,*)
60    write(num_rep_42,*) 'seuil_sedim    = ', seuil_sedim 
61    write(num_rep_42,*) 'coefmax        = ', coefmax
62    write(num_rep_42,*) 'Cfs            = ', Cfs
63    write(num_rep_42,*)'/'
64    write(num_rep_42,428) '! seuil_sedim : seuil pour passer en stream si zone sediment'
65    write(num_rep_42,428) '! coefmax : hauteur d eau max dans le sediment (=hwatermax)'
66    write(num_rep_42,428) '! Cfs : coefficient de la loi de frottement sediment'
67
68
69!coefmax=hwatermax
70!seuil_sedim=0.0001
71
72! fichier mask fourni par l'intercomparaison Heino
73! on refait la lecture
74
75!      filin='mask-shelf-40.dat'
76
77!      filin = TRIM(DIRNAMEINP)//TRIM(filin)
78
79!       write(42,*) 'type de socle '
80!       write(42,*) 'mksedim donne par ',filin
81
82!open(11,file=filin)
83!do i=1,6
84!      read(11,*)  ! 6 lignes de commentaires
85!end do
86
87
88! lecture proprement dite de la carte sediment
89!do j=ny, 1, -1
90!    read(11,'(87i1)') (mksedim(i,j), i=1,nx)
91!end do
92
93
94!close(11)
95
96! test pour une calotte axi-symetrique avec glissement Cr partout
97!write(num_rep_42,*) 'masque sediment mis a 1 '
98!mksedim(:,:)=min(mksedim(:,:),1)
99
100! a la frontiere le demi noeud est sediment.
101! calcul du masque sur les demi mailles : frontiere -> sedim
102!mkxsedim(:,:)=max(mksedim(:,:),eoshift(mksedim(:,:),shift=-1,boundary=0,dim=1))
103!mkysedim(:,:)=max(mksedim(:,:),eoshift(mksedim(:,:),shift=-1,boundary=0,dim=2))
104! write(42,*) 'sur les bords zone sediment, masque exterieur '
105
106!if ((loigliss.eq.5).and.(Cs.gt.1.)) then
107    coefdrag=rog/Cfs
108    Cfs=0.
109    write(42,*)'dragging Heino'
110    write(42,*)'passage en stream si zone sediment + fusion'
111    write(42,*)'coefficient de frottement dans la zone sediment (Pa/m)=',coefdrag
112!endif
113
114  end subroutine init_dragging
115
116!> SUBROUTINE: dragging
117!! Defini le basal drag
118!<
119
120  subroutine dragging   
121
122! dans la zone sediment : appele si loigliss=5,
123! defini le basal drag
124
125
126!flgzmx(:,:)=.false.
127!flgzmy(:,:)=.false.
128
129    betamx(:,:)=1.e5
130    betamy(:,:)=1.e5
131
132    shelfy=.false.
133
134
135
136    call moy_mxmy(nx,ny,Hwater,hw_mx,hw_my)
137
138    froty: do j=2,ny
139       do i=2,nx-1
140
141          if (mkysedim(i,j).eq.2) then  ! loi sediment
142
143            ! seulement si au dessus du point de fusion
144!            if ((T(i,j,nz).lt.Tpmp(i,j,nz)).or.(T(i,j-1,nz).lt.Tpmp(i,j-1,nz))) then
145             if (hw_my(i,j).ge.seuil_sedim) then
146                if (.not.flot(i,j)) then
147                   gzmy(i,j)=.true.
148                   coefslid=hw_my(i,j)
149                   coefslid=max(coefslid,seuil_sedim)
150                   coefslid=min(coefslid/coefmax,1.)
151                   betamy(i,j)=min(coefdrag/coefslid,1.e5)
152
153!               betamy(i,j)=coefdrag
154
155
156                   flgzmy(i,j)=.true.
157                   ddby(i,j)=0.
158                   mslid_my(i,j)=5
159                   shelfy=.true.
160                endif
161             endif
162          endif
163
164       end do
165    end do froty
166
167
168    frotx: do j=2,ny-1
169       do i=2,nx
170
171          if (mkxsedim(i,j).eq.2) then  ! loi sediment
172
173            ! seulement si au dessus du point de fusion
174!            if ((T(i,j,nz).lt.Tpmp(i,j,nz)).or.(T(i-1,j,nz).lt.Tpmp(i-1,j,nz))) then
175             if (hw_mx(i,j).ge.seuil_sedim) then
176                if (.not.flot(i,j)) then
177                   gzmx(i,j)=.true.
178                   coefslid=hw_mx(i,j)
179                   coefslid=max(coefslid,seuil_sedim)
180                   coefslid=min(coefslid/coefmax,1.)
181                   betamx(i,j)=min(coefdrag/coefslid,1.e5)
182
183!               betamx(i,j)=coefdrag
184
185                   flgzmx(i,j)=.true.
186                   ddbx(i,j)=0.
187                   mslid_mx(i,j)=5
188                   shelfy=.true.
189                endif
190             endif
191           
192          endif
193       end do
194    end do frotx
195
196!   gzmx(:,:)=flgzmx(:,:)
197!   gzmy(:,:)=flgzmy(:,:)
198!   gzmx_heino(:,:)=gzmx(:,:)
199!   gzmy_heino(:,:)=gzmy(:,:)
200
201
202    return
203  end subroutine dragging
204
205
206END MODULE dragging_hudson
207
208
Note: See TracBrowser for help on using the repository browser.