source: branches/GRISLIv3/SOURCES/isostasie_mod-0.3.f90 @ 483

Last change on this file since 483 was 481, checked in by aquiquet, 4 months ago

Cleaning branch: unused variables removed following strict compilation

File size: 3.9 KB
Line 
1!> \file isostasie_mod-0.3.f90
2!!Package isostasie
3!<
4
5!> \namespace isostasie_mod
6!! Module pour le calcul de l'isostasie
7!! \author ...
8!! \date ...
9!! @note Used modules
10!! @note    - use iso_declar
11!! @note    - use module3D_phy
12!! @note    - use param_phy_mod
13!<
14
15
16
17module isostasie_mod
18
19   use geography, only: nx,ny 
20   use iso_declar,only: nbed 
21
22   implicit none
23
24   real,dimension(nx,ny) :: W0           !< enfoncement du socle a l'equilibre isostatique
25   real,dimension(nx,ny) :: W1           !< enfoncement du socle courant
26
27contains
28
29!> SUBROUTINE: init_iso
30!! Routine qui permet d'initialiser les variables
31!>
32  subroutine init_iso ! routine qui permet d'initialiser les variables
33
34    use iso_declar,only: nlith,dt_iso,tausoc,dl,rl,lbloc,we,charge
35    use module3D_phy, only: err,h0,bsoc0,sealevel_2d
36    use geography, only: geoplace,nx,ny,dx,dy
37    use param_phy_mod, only: ro,row,rog,rowg,romg
38
39    implicit none
40
41    !     nbed=0 pas d'isostasie
42    !     nbed=1 temps de reaction
43
44    integer :: i,j
45
46    NBED=1
47    NLITH=1
48
49    !      temps de reaction en annees
50    if (NBED.eq.1) tausoc=3000
51
52    if (NLITH.eq.1) then
53       !        DL lithosphere flexural rigidity (N.m)
54       DL=9.87E24
55       !        radius of relative stiffness  (metre)
56       RL=131910.
57       !        LBLOC, 400 km de part et d'autre
58       LBLOC=int((400000.-0.1)/DX)+1
59       !         LBLOC=int((480000.-0.1)/DX)+1
60       !         LBLOC=int(400000./DX)+1
61
62
63       !******** allocation des tableaux en fonction de la valeur de LBLOC *****
64
65       if (.not.allocated(WE)) then
66          allocate(WE(-LBLOC:LBLOC,-LBLOC:LBLOC),stat=err)
67          if (err/=0) then
68             print *,"Erreur a l'allocation du tableau WE",err
69             stop 4
70          end if
71       end if
72       !    PRINT*,'shape(we)',SHAPE(we),'lbloc',lbloc
73
74       if (.not.allocated(CHARGE)) then
75          allocate(CHARGE(1-LBLOC:NX+LBLOC,1-LBLOC:NY+LBLOC),stat=err)
76          if (err/=0) then
77             print *,"Erreur a l'allocation du tableau CHARGE",err
78             stop 4
79          end if
80       end if
81       !********* FIN DE L'ALLOCATION DES TABLEAUX ***********
82       call tab_litho
83    end if
84
85    !******** initialisation de CHARGE ***********
86
87    !       pour calcul du socle initial on calcule la charge
88    !       avec l'etat initial suppose en equilibre S0, H0, Bsoc0
89
90    do i=1,nx
91       do j=1,ny
92          if (ro*h0(i,j).ge.-row*(BSOC0(i,j)-sealevel_2d(i,j))) then
93
94             !        glace ou terre
95             charge(i,j)=rog*h0(i,j)
96
97          else
98             !        ocean
99             charge(i,j)=-rowg*(Bsoc0(i,j)-sealevel_2d(i,j))
100          endif
101       end do
102    end do
103
104    do j=1,ny  ! parties de charge a l'exterieure de la grille
105       charge(1-lbloc:0,j)=charge(1,j)
106       charge(nx+1:nx+lbloc,j)=charge(nx,j)
107    end do
108    do i=1,nx
109       charge(i,1-lbloc:0)=charge(i,1)
110       charge(i,ny+1:ny+lbloc)=charge(i,ny)
111    end do
112
113    do j=1,ny  ! parties de charge a l'exterieure de la grille
114       charge(1-lbloc:0,j)=charge(1,j)
115       charge(nx+1:nx+lbloc,j)=charge(nx,j)
116    end do
117    do i=1,nx
118       charge(i,1-lbloc:0)=charge(i,1)
119       charge(i,ny+1:ny+lbloc)=charge(i,ny)
120    end do
121    charge(1-lbloc:0,1-lbloc:0)=charge(1,1) !valeurs aux quatres coins
122    charge(1-lbloc:0,ny+1:ny+lbloc)=charge(1,ny) ! exterieurs au domaine
123    charge(nx+1:nx+lbloc,1-lbloc:0)=charge(nx,1)
124    charge(nx+1:nx+lbloc,ny+1:ny+lbloc)=charge(nx,ny)
125
126    !     deflection de la lithosphere
127    if (nlith.eq.1) then
128
129       call litho
130
131       do j=1,ny
132          do i=1,nx
133             w0(i,j)=w1(i,j)
134          end do
135       end do
136    else
137       do j=1,ny
138          do i=1,nx
139             w0(i,j)=charge(i,j)/romg
140          end do
141       end do
142    end if
143
144    dt_iso = 50.
145
146  end subroutine init_iso
147
148
149
150!> SUBROUTINE: bedrock
151!! Routine qui calcule l'isostasie
152!>
153
154subroutine bedrock
155  call taubed  ! routine qui calcule l'isostasie
156end subroutine bedrock
157
158end module isostasie_mod
Note: See TracBrowser for help on using the repository browser.