source: branches/iLoveclim/SOURCES/Old-sources/eq_elliptique_mod-0.4.f90 @ 77

Last change on this file since 77 was 77, checked in by dumas, 8 years ago

Merge branche iLOVECLIM sur rev 76

  • Property svn:mime-type set to application/octet-stream
File size: 3.8 KB
Line 
1!> \file eq_elliptique_mod-0.4.f90
2!!Module pour la resolution des equations elliptiques de l'ice shelf
3!<
4
5!> \namespace eq_elliptique_mod
6!! Module pour la resolution des equations elliptiques de l'ice shelf
7!! \author ...
8!! \date ...
9!! @note Used module
10!! @note   - use module3D_phy
11!<
12module eq_elliptique_mod
13
14
15! declaration des variables
16
17implicit none
18
19integer :: kl,ku,kdc2   
20integer :: ldbmax   ! largeur de bande maximum (taille de la matrice) >= 2kl+ku+1
21integer :: nptmax   ! nombre maximum de points dans le domaine
22
23
24!      parameter (NPTMAX=15000) ! en 40km
25!      parameter (NPTMAX=60000) ! en 20km
26
27real,dimension(:,:), allocatable::BDR
28real,dimension(:,:), allocatable::MMAT
29real,dimension(:),   allocatable::BDRO
30
31!      real BDR(NPTMAX,1),MMAT(LDBMAX,NPTMAX),BDRO(NPTMAX)
32
33
34CONTAINS
35
36!> SUBROUTINE: initial_matrice
37!!@note Routine pour l'initialisation des matrices
38!<
39subroutine initial_matrice
40
41  USE module3D_phy
42
43! we initialize NPTMAX and LDBMAX
44  if (geoplace.eq.'anteis1') then
45                                ! for the 40km grid:
46     kl=284 ! 2*141
47     ku=284
48     NPTMAX=39762 ! 40km grid : 2*nx*ny=2*141**2
49!     parameter (NPTMAX=39762) ! 40km grid : 2*nx*ny=2*141**2
50! On initialise la matrice maximale car remplimat_rescue calcul
51! sur tout le domaine
52!    kl=171
53!    ku=171
54!    NPTMAX=2000!10000
55  elseif (geoplace.eq.'ant20km') then
56                                ! for the 20km grid:
57     kl=341
58     ku=341
59     NPTMAX=60000
60  elseif (geoplace(1:5).eq.'hemin') then
61     kl=400
62     ku=400
63     NPTMAX=90000
64  else
65     kl=nx+ny
66     ku=nx+ny
67     NPTMAX=2*nx*ny     
68  endif
69     kdc2=KL+KU+1
70     LDBMAX=2*KL+KU+1
71     
72  if (.not.allocated(BDR)) THEN
73     allocate(BDR(NPTMAX,1),stat=err)
74     if (err/=0) then
75        print *,"Erreur à l'allocation du tableau BDR",err
76        stop 4
77     end if
78  end if
79  if (.not.allocated(MMAT)) THEN
80     allocate(MMAT(LDBMAX,NPTMAX),stat=err)
81     if (err/=0) then
82        print *,"Erreur à l'allocation du tableau MMAT",err
83        stop 4
84     end if
85  end if
86  if (.not.allocated(BDRO)) THEN
87     allocate(BDRO(NPTMAX),stat=err)
88     if (err/=0) then
89        print *,"Erreur à l'allocation du tableau BDRO",err
90        stop 4
91     end if
92  end if
93     
94    print*,'LDBMAT',LDBMAX
95 print*,'NPTMAT',NPTMAX
96
97 END subroutine INITIAL_MATRICE 
98
99!> SUBROUTINE: definition_matrice
100!! Routine pour les definition des matrices
101!! \param initi
102!! \param nptmat
103!! \param ldbmat
104!>
105subroutine definition_matrice(initi,nptmat,ldbmat)
106
107USE module3D_phy
108   
109      logical INITI
110      INTEGER NPTMAT
111      INTEGER LDBMAT
112     
113initiation : IF (INITI) THEN
114     
115        print *,"Erreur mauvais appel a DEFINITION_MATRICE"
116        ELSE !initia
117
118!here we recall DEFINITION_MATRICE cause the former matrices
119!have become too shallow
120!neow allocation with new NPTMAT,LDBMAT sent by remplimat   
121   print *,"realocation" 
122   print*,'NPTMAT',NPTMAT
123   print*,'LDBMAT',LDBMAT
124   
125   deallocate(BDR,MMAT,BDRO,stat=err)
126     if (err/=0) then
127        print *,"Erreur à la desallocation des tableau BDR,MMAT,BDRO",err
128        stop 4
129     end if
130 
131   if (.not.allocated(BDR)) THEN
132     allocate(BDR(NPTMAT,1),stat=err)
133     if (err/=0) then
134        print *,"Erreur à la re-allocation du tableau BDR",err
135        stop 4
136     end if
137  end if
138  if (.not.allocated(MMAT)) THEN
139     allocate(MMAT(LDBMAT,NPTMAT),stat=err)
140     if (err/=0) then
141        print *,"Erreur à la re-allocation du tableau MMAT",err
142        stop 4
143     end if
144  end if
145  if (.not.allocated(BDRO)) THEN
146     allocate(BDRO(NPTMAT),stat=err)
147     if (err/=0) then
148        print *,"Erreur à la re-allocation du tableau BDRO",err
149        stop 4
150     end if
151  end if
152        ENDIF initiation
153
154END subroutine DEFINITION_MATRICE
155
156!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
157!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
158
159
160
161END MODULE EQ_ELLIPTIQUE_MOD
Note: See TracBrowser for help on using the repository browser.