source: trunk/SOURCES/courbures.f90 @ 23

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

initial import GRISLI trunk

File size: 7.0 KB
Line 
1!> \file courbures.f90
2!! Implementation du subroutine courbure
3!<
4
5!> SUBROUTINE: courbure
6!! \author ...
7!! \date ...
8!! @note Subroutine qui permet de trouver la surface de type
9!! @note A_2D(x,y)=ax2+by2+cxy+dx+ey+f 
10!! @note passant au plus pres (moindre carre) des 9 points d'une sous grille
11!! @note Ensuite, calcule les diverses courbures, la pente et son azimuth
12!! @note Le pas de la grille est 1     
13!! @note Fait appel a sgelsy  de Lapack qui minimise || A * X -B ||
14!>
15subroutine courbure(nx,ny,dy,A_2D,A_new,pente_A,teta_A,crx,cry,crxy)
16
17implicit none
18
19integer mnode,ncoef,npts
20
21! entree routine
22
23integer,intent(in) :: nx,ny         !< dimensions des matrices 
24real,intent(in)    :: dy            !< maille physique
25real,dimension(nx,ny),intent(in) :: A_2D  !< la surface dont on cherche la courbure
26
27! sortie routine
28real,dimension(nx,ny),intent(out):: A_new      !< altitude finale du point
29real,dimension(nx,ny),intent(out):: pente_A    !< pente_A (amplitude)
30real,dimension(nx,ny),intent(out):: teta_A     !< direction de la pente
31real,dimension(nx,ny),intent(out):: crx        !< courbure dans la direction de la pente 
32real,dimension(nx,ny),intent(out):: cry        !< courbure dans la direction transversale
33real,dimension(nx,ny),intent(out):: crxy       !< courbure croisee
34
35
36! variables locales
37parameter(mnode=9)          !< nombre de points de la sous-grille
38parameter (ncoef=6)         !< nombre de coefficients de A_2D
39parameter (npts=60000)      !< nombre de points a traiter (nx*ny)
40
41
42real,dimension(mnode) :: Z_sg               !< altitude des points de la sous-grille
43real :: dx_ls                               !< pas de la grille dans le moindre carre
44real,dimension(ncoef) :: acoef              !< matrice de coef pour construction
45integer :: i,j,k,l,pp,iz,jz,iz1,jz1         !< compteurs
46real :: x,y                                 !< coordonnees dans la sous-grille
47real :: aaa                                 !< pour le calcul de l'azimut
48
49
50! specifiques pour appel a sgelsy
51real :: Blin(mnode,npts)            !< en input c'est B(mnoeud,npts)
52                                    !< en output c'est X(ncoef,npts)
53real :: A(mnode,ncoef)              !< matrice A
54real :: rcond                       !< pour appel a sgelsy  ~ max(A)/min(A)
55integer :: rank                     !< pour sgelsy (output) -> rang de R11
56integer :: lwork                    !< taille du tableau de travail
57parameter(lwork = 200000)           !< voir sgelsy
58real,dimension(lwork) :: work       !< tableau de travail
59integer,dimension(ncoef):: jpvt     !< vecteur entier
60integer :: info                     !< retour des info
61integer :: mm,nn,npp,lw
62       
63
64mm=mnode                            ! pour ne pas passer des
65nn=ncoef                            ! constantes aux routines
66npp=npts                           
67lw=lwork                       
68
69dx_ls=1                             ! pas utilise dans le moindre carre
70
71
72
73
74!      remplissage de la matrice A (la meme pour tous les points)
75
76k=0
77do j=-1,1            !                                   7   8   9
78   do i=-1,1         ! balaye les i puis les j           4   5   6
79      k=k+1          ! k varie de 1 a 9                  1   2   3
80      x=i*dx_ls
81      y=j*dx_ls
82     
83      A(k,1)=x*x
84      A(k,2)=y*y
85      A(k,3)=x*y
86      A(k,4)=x
87      A(k,5)=y
88      A(k,6)=1
89   end do
90end do
91
92rcond=1.e-30
93
94
95!     boucle sur les points
96pp=0
97ij_loop: do j=1,ny
98pp_loop:   do i=1,nx
99      pp=pp+1            ! pp varie de 1 a nx*ny
100     
101
102!       Construction de la sous-grille centree sur i,j
103      k=0
104      do jz=j-1,j+1
105         do iz=i-1,i+1
106            iz1=max(1,iz)      ! pour éviter les débordements du tableau A_2D
107            iz1=min(nx,iz1)
108            jz1=max(1,jz)
109            jz1=min(ny,jz1)
110
111            k=k+1              ! k varie de 1 a 9
112
113            Blin(k,pp)=A_2D(iz1,jz1)
114         end do
115      end do
116
117   end do pp_loop
118end do ij_loop 
119
120!____________________________________________________________________
121!
122!  appel a la subroutine sgelsy
123!____________________________________________________________________
124
125call sgelsy(mm,nn,npp,a,mm,blin,mm,jpvt,rcond,rank,work,lw,info)
126
127 
128!       Maintenant les coefficients sont dans Blin(1:6,pp)
129!        Blin(1,pp)= a    coeff de x2
130!        Blin(2,pp)= b    coeff de y2
131!        Blin(3,pp)= c    coeff de xy
132!        Blin(4,pp)= d    coeff de x
133!        Blin(5,pp)= e    coeff de y
134!        Blin(6,pp)= f    terme constant
135
136pp=0
137grille_loop: do j=1,ny
138   do i=1,nx
139      pp=pp+1
140      A_new(i,j)=Blin(6,pp)                                    ! f
141      pente_A(i,j)=Blin(4,pp)*Blin(4,pp)+Blin(5,pp)*Blin(5,pp) ! d2+e2
142     
143
144
145pente_sup0:  if ((pente_A(i,j).gt.1.e-5)   &
146                .and.(i.ne.1).and.(i.ne.nx).and.(j.ne.1).and.(j.ne.ny))  then
147
148! pente
149         pente_A(i,j)=(pente_A(i,j)**0.5)                    ! attention ce calcul etait avant fait
150                                                             ! apres le calcul de courbure.
151                                                             ! Par comparaison avec Frederique, c'etait un bug.
152
153
154! courbx
155         crx(i,j)=blin(1,pp)*blin(4,pp)*blin(4,pp)     &     ! ad2
156               +  blin(2,pp)*blin(5,pp)*blin(5,pp)     &     ! be2
157               +  blin(3,pp)*blin(4,pp)*blin(5,pp)           ! cde
158
159         crx(i,j)=2.*crx(i,j)/pente_A(i,j)/dy/dy             ! dy2 pour
160                                                             ! passage en dim reelle
161
162! courby
163         cry(i,j)=blin(1,pp)*blin(5,pp)*blin(5,pp)     &     ! ae2
164               +  blin(2,pp)*blin(4,pp)*blin(4,pp)     &     ! bd2
165               -  blin(3,pp)*blin(4,pp)*blin(5,pp)           ! -cde
166               
167         cry(i,j)=2.*cry(i,j)/pente_A(i,j)/dy/dy             ! dy2 pour
168                                                             ! passage en dim reelle
169
170! courbxy
171         crxy(i,j)=2.*blin(1,pp)*blin(4,pp)*blin(5,pp)  &    ! 2ade
172                -  2.*blin(2,pp)*blin(4,pp)*blin(5,pp)  &    ! -2bed
173                -  blin(3,pp)*blin(4,pp)*blin(4,pp)     &    ! -cd2
174                -  blin(3,pp)*blin(5,pp)*blin(5,pp)          ! -ce2
175               
176         crxy(i,j)=crxy(i,j)/pente_A(i,j)/dy/dy              ! dy2 pour
177                                                             ! passage en dim reelle
178
179
180
181! direction de la pente
182         aaa=blin(5,pp)/pente_A(i,j)                         ! pente y / pente
183
184         if ((aaa.gt.-1.).and.(aaa.lt.1.)) then
185            teta_A(i,j)=asin(aaa)*180./3.14159
186         else if (aaa.ge.1.) then
187            teta_A(i,j)=90.
188         else if (aaa.le.-1.) then
189            teta_A(i,j)=-90.
190         endif
191
192         if (blin(4,pp).lt.0.) then
193            teta_A(i,j)=180.-teta_A(i,j)
194         endif
195         
196      else            ! pente nulle
197         crx(i,j)=0.
198         cry(i,j)=0.
199         crxy(i,j)=0.
200         pente_A(i,j)=0.
201         teta_A(i,j)=0.
202       
203      endif pente_sup0 !  Fin du test sur la pente
204
205! pente
206      pente_A(i,j)=pente_A(i,j)/dy     ! pour passage en dimension reelle
207
208   end do
209end do grille_loop                     !   fin de la boucle sur les points de grille
210   
211 
212return 
213end subroutine courbure
Note: See TracBrowser for help on using the repository browser.