Está en la página 1de 71

NOTAS DE CLASE

Tema: Ajuste de datos por mínimos cuadrados


(lineal y no lineal)
Fitting data: linear least square method

Interpolation

?
Fitting
Fitting data: linear least square method
Sea un conjunto de n puntos del plano
M = {(x1,y1); (x2,y2); …;(xn,yn)} con i=1,…,n

Interpolation

- Si los pares (xi;yi) son resultados de alguna


medición o cálculo aproximado,
existen incertezas. Fitting
- A veces se cuenta además con información
adicional del fenómeno que representan los datos
(por ejemplo: qué comportamiento deberían presentar).
Conviene encontrar una función F(x) que se aproxime a los datos
Fitting data: linear least square method
Sea un conjunto de n puntos del plano
M = {(x1,y1); (x2,y2); …;(xn,yn)} con i=1,…,n

y Para el método que presentaremos a


continuación “da lo mismo” si los
escalares yi son función de un escalar
x (variable independiente) o si la
variable independiente es un conjunto
de N escalares (i.e. x є RN):

M = {(x1,y1); (x2,y2); …;(xn,yn)}


con i=1,…,n
x
Fitting data: linear least square method
Sea un conjunto de n puntos del plano
M = {(x1,y1); (x2,y2); …;(xn,yn)} con i=1,…,n

y Para el método que presentaremos a


continuación “da lo mismo” si los
escalares yi son función de un escalar
x (variable independiente) o si la
variable independiente es un conjunto
de N escalares (i.e. x є RN):

M = {(x1,y1); (x2,y2); …;(xn,yn)}


con i=1,…,n
x

Vamos a buscar una función F [ (R → R) o F(RN→R) ] que al ser evaluada


en el conjunto {x1, x2, …, xn}, se obtenga el conjunto de valores
{F(x1), F(x2), …, F(xn)} que sea “lo más próximo posible” al conjunto {y1, y2, …, yn}
Fitting data: linear least square method

(*)
Fitting data: linear least square method

If:

є Rn

U U┴

U||
L

(**)
(*)
(**) Theorem:
(**) Theorem:
Fitting data: linear least square method

If:
Example: linear fitting

Z Y

a*=(ZT.Z)-1. ZT.Y
Example: linear fitting

e = Y - Z . a*
A Fortran code for linear fitting
program linear_least_squares
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
implicit none
integer(4) :: i,n,m ! n: number of data; m=number of fitting parameters
real(8), allocatable :: x(:),y(:) ! data
real(8), allocatable :: a(:) ! fitting parameters
real(8),allocatable :: z(:,:),zt(:,:),ztz(:,:),inv_ztz(:,:),prodm(:,:),identity(:,:)
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
open(10,file='data_linear.in',status='old') ! Start reading data
read(10,*) n
print *, 'Number of data:',n
allocate (x(n),y(n))
print *,' Data:'
do i=1,n
read(10,*)x(i),y(i)
print *,x(i),y(i)
enddo
read(10,*) m
print *, 'Number of parameters to be optimized:',m
close(10) ! End reading data
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
allocate(z(n,m)) ; call zmatrix(n,x,m,z) ! computing Z_(nxm)
allocate(zt(m,n)) ; zt=transpose(z) ! computing the transpose of Z_(nxm)
allocate(ztz(m,m)) ; ztz=matmul(zt,z) ! computing Z_(nxm)^t . Z_(nxm)

allocate(identity(m,m),inv_ztz(m,m)) ! computing [Z_(nxm)^t . Z_(nxm) ]^-1


identity=0._8
do i=1,m
identity(i,i)=1._8
end do
call elim_gauss_jordan_pivoteo_parcial_msist(m,ztz,m,identity,inv_ztz)

allocate(prodm(m,n)) ; prodm=matmul(inv_ztz,zt) ! [Z_(nxm)^t . Z_(nxm) ]^-1 . Z_(nxm)^t


allocate(a(m)) ; a=matmul(prodm,y) ! a = [Z_(nxm)^t . Z_(nxm) ]^-1 . Z_(nxm)^t . y
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
print *,'Best fitting parameters, a=',a
deallocate (x,y,z,zt,ztz,inv_ztz,prodm,a)
end program linear_least_squares
A Fortran code for linear fitting
program linear_least_squares
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
implicit none
integer(4) :: i,n,m ! n: number of data; m=number of fitting parameters
real(8), allocatable :: x(:),y(:) ! data
real(8), allocatable :: a(:) ! fitting parameters !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
real(8),allocatable :: z(:,:),zt(:,:),ztz(:,:),inv_ztz(:,:),prodm(:,:),identity(:,:) subroutine zmatrix(n,x,m,z)
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! implicit none
open(10,file='data_linear.in',status='old') ! Start reading data integer(4) :: i,n,m
read(10,*) n real(8) :: x(n),z(n,m)
print *, 'Number of data:',n do i=1,n
allocate (x(n),y(n)) call functions(x(i),m,z(i,:))
print *,' Data:' enddo
do i=1,n end subroutine zmatrix
read(10,*)x(i),y(i) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
print *,x(i),y(i) subroutine functions(x,m,funcs)
enddo implicit none
read(10,*) m integer(4) :: m
print *, 'Number of parameters to be optimized:',m real(8) :: x
close(10) ! End reading data real(8) :: funcs(m)
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! funcs(1)=1._8
allocate(z(n,m)) ; call zmatrix(n,x,m,z) ! computing Z_(nxm) funcs(2)=x
allocate(zt(m,n)) ; zt=transpose(z) ! computing the transpose of Z_(nxm) end subroutine functions
allocate(ztz(m,m)) ; ztz=matmul(zt,z) ! computing Z_(nxm)^t . Z_(nxm) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

allocate(identity(m,m),inv_ztz(m,m)) ! computing [Z_(nxm)^t . Z_(nxm) ]^-1


identity=0._8
do i=1,m data_linear.in
identity(i,i)=1._8
end do
call elim_gauss_jordan_pivoteo_parcial_msist(m,ztz,m,identity,inv_ztz)
4 <-- n
1. 1. <-- | data
allocate(prodm(m,n)) ; prodm=matmul(inv_ztz,zt) ! [Z_(nxm)^t . Z_(nxm) ]^-1 . Z_(nxm)^t
allocate(a(m)) ; a=matmul(prodm,y) ! a = [Z_(nxm)^t . Z_(nxm) ]^-1 . Z_(nxm)^t . y
2. 2. |
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 3. 2. |
print ,'Best fitting parameters, a=',a,‘chi2=’,norm2(matmul(z,a)-y)**2.
deallocate (x,y,z,zt,ztz,inv_ztz,prodm,a)
4. 3. |
end program linear_least_squares 2 <-- m
Example: linear fitting
Non-linear least squares: Gauss-Newton method
Non-linear least squares: Gauss-Newton method
Example: non-linear regression (Gauss-Newton)
Example: non-linear regression (Gauss-Newton)

Let’s write a Fortran


code to solve
non-linear least square
problems iteratively
A Fortran code for non-linear fitting
program gaussnewton
implicit none
integer(4) :: i,j,nmax
integer(4) :: n,m
real(8), allocatable :: x(:),y(:),fit(:)
real(8), allocatable :: a(:)
real(8) :: error2,error2new
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
open(10,file='data.in',status='old') ! Start reading data
read(10,*) n
print *, 'Number of data:', n print *, '%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%'
allocate (x(n),y(n),fit(n)) print *, 'STARTING ITERATIONS'
do i=1,n do i=1,nmax
read(10,*)x(i),y(i) call optim(x,y,fit,a,n,m)
print *, x(i),y(i) do j=1,n
enddo call func(x(j),m,a,fit(j))
read(10,*) m enddo
print *, 'Number of fit parameters:', m error2new=0.d0
print *, 'Initial parameters a:' do j=1,n
allocate(a(m)) error2new=error2new+(y(j)-fit(j))**2.d0
do i=1,m enddo
read(10,*)a(i) print *, 'New vector a:'
print *, a(i) do j=1,m
enddo print *, a(j)
read(10,*) nmax enddo
print *, 'Maximum number of iterations:',nmax print *, ' '
close(10) ! End reading data print *, 'After iteration:',i,'error=',sqrt(error2new)
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! Print *, '%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%'
do i=1,n ! Computing the initial "error" if (abs(error2new-error2)/error2new < 1.d-6) then
call func(x(i),m,a,fit(i)) print *, 'GOOD NEWS: After',i,'iterations, desired accuracy obtained'
enddo stop
error2=0.d0 elseif (i == nmax) then
do i=1,n print *, 'BAD NEWS: After',nmax,'iterations, desired accuracy NOT reached'
error2=error2+(y(i)-fit(i))*(y(i)-fit(i)) else
enddo error2=error2new
print *, 'Initial error=',sqrt(error2) endif
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! enddo
deallocate (a,x,y,fit)

end program gaussnewton


A Fortran code for non-linear fitting
subroutine optim(x,y,fit,a,n,m)
implicit none
integer(4) :: i,n,m
real(8) :: x(n),y(n),fit(n),d(n)
real(8) :: a(m)
real(8) :: z(n,m),prod(m,m),identity(m,m),prodm1(m,m)
call zmatrix(n,x,m,a,z)
prod=matmul(transpose(z),z)
identity=0._8
do i=1,m
identity(i,i)=1._8
end do
call elim_gauss_jordan_pivoteo_parcial_msist(m,prod,m,identity,prodm1) ! [Z_(nxm)^t . Z_(nxm) ]^-1
d=y-fit
a=a+matmul(prodm1,matmul(transpose(z),d))
end subroutine optim
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
subroutine zmatrix(n,x,m,a,z)
implicit none
integer(4) :: i,n,m
real(8) :: x(n),a(m),z(n,m)
do i=1,n
call gradfunc(x(i),m,a,z(i,:))
enddo
end subroutine zmatrix
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
subroutine func(x,m,a,f)
implicit none
integer(4) :: m
real(8) :: x,a(m),f
f=a(1)*exp(a(2)*x)
end subroutine
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
subroutine gradfunc(x,m,a,gradf)
implicit none
integer(4) :: m
real(8) :: x,a(m),gradf(m)
gradf(1)=exp(a(2)*x)
gradf(2)=a(1)*x*exp(a(2)*x)
end subroutine gradfunc
A Fortran code for non-linear fitting
Number of data: 5
0.25000000000000000 0.28000000000000003
0.75000000000000000 0.56999999999999995
1.2500000000000000 0.68000000000000005 data.in
1.7500000000000000 0.73999999999999999
2.2500000000000000 0.79000000000000004
Number of fit parameters: 2 5 <-- ndata
Initial parameters a: 0.25 0.28 <--| data
1.0000000000000000 0.75 0.57 |
1.0000000000000000 1.25 0.68
Maximum number of iterations: 100 1.75 0.74
Initial error= 0.15732336306057984 2.25 0.79
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
STARTING ITERATIONS 2 <-- m
New vector a: 1.0 <--| initial fitting param
0.72852264001541789 1.0 |
1.5019308677020646
100 <-- nmax: maximum number of iterations
After iteration: 1 error= 0.15569428644174324
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
New vector a:
0.79104310274117062 f(x;a1,a2) = a1 . [1 – exp(- a2 . x)]
1.6777011225373202

After iteration: 2 error= 2.5742753682923624E-002


%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
New vector a:
0.79185177283167896
1.6752684438737255

After iteration: 3 error= 2.5722739931262562E-002


%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
New vector a:
0.79186690226172107
1.6751459046438626

After iteration: 4 error= 2.5722732989475160E-002


%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
GOOD NEWS: After 4 iterations, desired accuracy obtained
FIN NOTAS DE CLASE

Tema: Ajuste de datos por mínimos cuadrados


(lineal y no lineal)
NOTAS DE CLASE

Tema: Interpolación
- como caso particular de fitting (m=n)
- polinomial: Lagrange y Newton
- segmentaria: splines
Interpolation vs. fitting methods

Interpolation
Fitting
Interpolation
Interpolation can be viewed as a VERY particular case of fitting, possible in SOME cases:

- xi ≠ xj for all i≠j


- L.I set of functions “large” enough to fit the data (linear least squares)
with error equal to zero (i.e. n=m)
Interpolation
Interpolation can be viewed as a VERY particular case of fitting, possible in SOME cases:

- xi ≠ xj for all i≠j


- L.I set of functions “large” enough to fit the data (linear least squares)
with error equal to zero (i.e. n=m)
Interpolation

E.g. {f1(x),f2(x),f3(x),f4(x),…,fn(x)}= {1,x,x2,x3,...xn-1} → Polynomial interpolation


{1,sin(x),sin(2x),sin(3x),…, sin[(n-1)x]} → Fourier interpolation
Polynomial Interpolation
Do polynomials always satisfy the necessary condition of linear independence of {fi}i=1,…,n ?

BUT often, finding the inverse of a big matrix entails large round errors
Polynomial Interpolation
FORMA DE LAGRANGE:
El matemático francés J. L. Lagrange descubrió que se puede encontrar
el polinomio interpolador usando un método distinto.

Consideremos ahora el siguiente conjunto de n+1 Nombre en francés:


polinomios de grado n:
Joseph-Louis Lagrange

Nacimiento: 25 de enero de 1736

Turín, Italia

Fallecimiento: 10 de abril de 1813

(77 años) en París, Francia

Lugar de sepultura: Panteón de París

Nacionalidad: Francesa

Lengua materna: Francés


Dividamos dichos polinomios por Ak(xk) con k=0,1,…n

Conjunto de
n+1 polinomios
de grado n

Polinomios
En forma general: coeficientes de
Lagrange
Propiedades de los polinomios Lk(n)(x):

Construyamos ahora el siguiente polinomio:

Forma de Lagrange del


Polinomio interpolante

El polinomio no necesariamente va a ser de grado n, sino que puede ser de grado menor que n

Existencia del polinomio interpolante garantizada !

Falta demostrar que el polinomio interpolante de grado <=n es único !


Using the Fundamental theorem of algebra:

"Every non-constant single-variable polynomial with complex coefficients has at


least one complex root"
FORMA DE LAGRANGE:

Ventajas:
• No es necesario resolver un sistema lineal de ecuaciones que
generalmente está mal condicionado
• Se puede conocer el valor del polinomio interpolante en un punto
intermedio cualquiera xp sin necesidad de conocer sus coeficientes ai
Desventajas (de la forma de Lagrange):
* Si queremos agregar un nuevo dato, hay que generar desde cero un nuevo polinomio
Fórmula de Newton

Desventaja (de la interpolación polinomial en general):


* Para n grande → oscilaciones espúreas
OSCILACIÓN POLINOMIAL: (Fenómeno de Runge)

Consideremos el error E n ( x)=f ( x )−Pn ( x )


Tiende a cero cuando n crece?

Para funciones como sin(x) o e-x, cuyas derivadas están acotadas por
una misma constante M, la respuesta es sí.

En general, sin embargo, la respuesta es no. Es fácil hallar funciones


donde el término del error En(x) crece cuando n →∞.
En estos casos, aparecen oscilaciones muy grandes cerca de los extremos

del intervalo y, si el número de puntos se incrementa, entonces las
oscilaciones se hacen aún mayores. Este problema ocurre generalmente
cuando los nodos están equiespaciados.

EJEMPLO

Aproximación polinomial a la función


1
f ( x )=
1+12 x 2
en el intervalo [-1, 1] utilizando
11 puntos equiespaciados
Polynomial Interpolation
FORMA DE NEWTON:

Isaac Newton
Nacimiento: 04/01/1643
Woolsthorpe Manor,
Reino Unido

Fallecimiento: 31/03/1727
Kingston, Londres

Entierro: Abadía de
Westminster, Londres
Polynomial Interpolation
FORMA DE NEWTON:

Isaac Newton
Nacimiento: 04/01/1643
Woolsthorpe Manor,
Reino Unido

Fallecimiento: 31/03/1727
Kingston, Londres

Entierro: Abadía de
Westminster, Londres
Polynomial Interpolation
FORMA DE NEWTON:
Polynomial Interpolation
FORMA DE NEWTON EN TERMINO DE DIFERENCIAS DIVIDIDAS:
Polynomial Interpolation

Desventaja (de la interpolación polinomial en general):


* Para n grande → oscilaciones espúreas

Aproximación polinomial a la función


1
f ( x )=
1+12 x 2
en el intervalo [-1, 1] utilizando
11 puntos equiespaciados
1D Interpolation methods
Polynomial interpolation:

Linear interpolation between consecutive knots looks better


than higher order interpolating polynomials !!
1D Interpolation methods
Splines interpolation:
1st-order: linear splines
2nd-order: quadratic splines
3rd-order: cubic splines

A spline is a numeric function that is


piecewise-defined by polynomial functions,
which possesses a high degree of smoothness
(as high as possible) at the places where the
polynomial pieces connect (which are known as knots).
1D Interpolation methods
Splines interpolation:

2nd-order: quadratic splines

n+1 data

3n unknown coefficients (3 per interval)

2n equations: interpolating conditions


+
n-1 equations: continuity of the 1st derivative

3n-1 equations → 1 missing equation

We can know or estimate the value of e.g. f’(x0),


or look for the value of f’(x0) that provides the most good-looking interpolating function
… any other additional condition to be fulfilled by the interpolating function
or its derivatives for any value of x is enough to solve the problem in a straightforward way
1D Interpolation methods
Splines interpolation:

2nd-order: quadratic splines

n+1 data

3n unknown coefficients (3 per interval)

2n equations: interpolating conditions


+
n-1 equations: continuity of the 1st derivative

3n-1 equations → 1 missing equation

We can know or estimate the value of e.g. f’(x0),


or look for the value of f’(x0) that provides the most good-looking interpolating function
… any other additional condition to be fulfilled by the interpolating function
or its derivatives for any value of x is enough to solve the problem in a straightforward way

If the extra condition involves the polinomial of the j-th interval, we can find first: aj,bj,cj, and
then move backward and forward (using the continuity conditions) to find all the coeficients
(i=j-1, j-2,…,1 and j+1,j+2,…,n) WITHOUT SOLVING ANY SET OF LINEAR EQUATIONS
1D cubic splines
Splines interpolation:
a3x3+b3x2+c3x+d3
Cubic splines
(the most popular ones) a1x +b1x +c1x+d1
3 2
a2x3+b2x2+c2x+d2

n+1 data
4n unknown coefficients (4 per interval)

2n equations: interpolating conditions

n-1 equations: continuity of the 1st derivative


+
n-1 equations: continuity of the 2nd derivative

4n-2 equations → 2 missing equation

We can know or estimate the value of e.g. f’(x0) and f’(xn),


or we can set f’’(x0)=f’’(xn)=0 (good for linear extrapolation): natural splines
The two conditions we have to add for periodic functions with period T=xn-x0:
f’(x0)=f’(xn) and f’’(x0)=f’’(xn) periodic splines
1D cubic splines
Splines interpolation:
a3x3+b3x2+c3x+d3
Cubic splines
(the most popular ones) a1x +b1x +c1x+d1
3 2
a2x3+b2x2+c2x+d2

n+1 data
4n unknown coefficients (4 per interval)

2n equations: interpolating conditions

n-1 equations: continuity of the 1st derivative


+
n-1 equations: continuity of the 2nd derivative

4n-2 equations → 2 missing equation

We can know or estimate the value of e.g. f’(x0) and f’(xn),


or we can set f’’(x0)=f’’(xn)=0 (good for linear extrapolation): natural splines
The two conditions we have to add for periodic functions with period T=xn-x0:
f’(x0)=f’(xn) and f’’(x0)=f’’(xn) periodic splines
If the extra conditions involve BOTH the polinomial of the j-th interval, we can find first: aj,bj,cj,dj
and then move backward and forward (using the continuity conditions) to find all the coeficients
(i=j-1, j-2,…,1 and j+1,j+2,…,n) WITHOUT SOLVING ANY SET OF LINEAR EQUATIONS
1D cubic splines
Splines interpolation:
a3x3+b3x2+c3x+d3
Cubic splines
(the most popular ones) a1x +b1x +c1x+d1
3 2
a2x3+b2x2+c2x+d2

n+1 data
4n unknown coefficients (4 per interval)

2n equations: interpolating conditions

n-1 equations: continuity of the 1st derivative


+
n-1 equations: continuity of the 2nd derivative

4n-2 equations → 2 missing equation

We can know or estimate the value of e.g. f’(x0) and f’(xn),


or we can set f’’(x0)=f’’(xn)=0 (good for linear extrapolation): natural splines
The two conditions we have to add for periodic functions with period T=xn-x0:
f’(x0)=f’(xn) and f’’(x0)=f’’(xn) periodic splines

Solving a 4nx4n set of linear equations would be the BRUTE-FORCE option: Not recommended !!
What to do to (at least) reduce the set of equations to solve ?
(if the extra conditions do not involve a single polynomial)
1D cubic splines
1D cubic splines
1D cubic splines
1D cubic splines
Splines interpolation:
a3x3+b3x2+c3x+d3
Cubic splines
Implementation a1x +b1x +c1x+d1
3 2
a2x3+b2x2+c2x+d2

Let’s take the interval i: [xi-1;xi]

The 2nd derivative of the 3rd order polynomial


is a linear function:

We integrate twice wrt x and we set the two


constants to obtain: fi(xi-1)=f(xi-1); fi(xi)=f(xi)

→ 2 unknowns: f’’(xi-1) ; f’’(xi)

i=1,…,n
1D cubic splines
Splines interpolation:
a3x3+b3x2+c3x+d3
Cubic splines
Implementation a1x +b1x +c1x+d1
3 2
a2x3+b2x2+c2x+d2

n+1 data

n+1 unknowns: f’’(xi) for i=0,…,n

n-1 equations: continuity of the 1st derivative


+
2 extra conditions
Compatible set of n+1 linear equations
with n+1 unknown: f’’(xi); i=0,…,n

Unique solution
fi(x)=Ai(x)f(xi-1)+Bi(x)f(xi)+Ci(x)f’’(xi-1)+Di(x)f’’(xi) i=1,…,n

Ai(x)=(xi-x)/(xi-xi-1)
IMPORTANT:
The matrix of coefficients depends on: Bi(x)=1-Ai(x)
- the set of knots: xi i=0,1,…,n
Ci(x)=[Ai(x)3-Ai(x)](xi-xi-1)2/6
- f(xi) i=0,1,…,n
Di(x)=[Bi(x)3-Bi(x)](xi-xi-1)2/6
1D cubic splines
Splines interpolation:
a3x3+b3x2+c3x+d3
Cubic splines
Implementation a1x +b1x +c1x+d1
3 2
a2x3+b2x2+c2x+d2

n+1 data

1st) Construction step (~ n):

We compute f’’(xi) i=0,…,n


by solving a (tridiagonal)
set of linear equation

ONLY ONCE !

2nd) Evaluation step :

a) Locate i / xi <= x <=xi+1


[~ log(n)] fi(x)=Ai(x)f(xi-1)+Bi(x)f(xi)+Ci(x)f’’(xi-1)+Di(x)f’’(xi) i=1,…,n

b) Evaluate fi(x) (trivial)


Ai(x)=(xi-x)/(xi-xi-1) Bi(x)=1-Ai(x)
AS MANY TIMES AS NEEDED Ci(x)=[Ai(x)3-Ai(x)](xi-xi-1)2/6 Di(x)=[Bi(x)3-Bi(x)](xi-xi-1)2/6
1D Cubic Splines exercise
splines1d.f90
program splines1d
implicit none
integer :: i,ndat,ncalc
real(8), allocatable :: x(:),y(:),y2(:)
real(8) :: yp1,ypn
real(8) :: x_int,y_int
open(10,file='interp1d.in',status='old')
read(10,*)ndat
allocate(x(ndat),y(ndat),y2(ndat))
read(10,*)yp1,ypn
do i=1,ndat
read(10,*)x(i),y(i)
enddo
close(10)
call spline(x, y, ndat, yp1, ypn, y2)
write(*,*)'Enter the number of points to interpolate'
read(*,*)ncalc
open(10,file='interp1d.out',status='unknown')
do i=1,ncalc
x_int=x(1)+(x(ndat)-x(1))*real(i-1)/real(ncalc-1)
call splint(x, y, y2, ndat, x_int, y_int)
write(10,102)x_int,y_int
enddo
close(10)
deallocate(x,y,y2)
102 format(2f15.8)
end program splines1d
1D Cubic Splines exercise
splines1d.f90
spline.f90

subroutine spline (x,y,n,yp1,ypn,y2) if (yp1.gt..99e30) then


!----------------------------------------------------------------------- y2(1) = 0.
! given arrays x(1:n) and y(1:n) containing a tabulated function, i.e. u(1) = 0.
! y_i = f(x_i), with x_1 < x_2 < ... < x_n, and given values yp1 ypn for else
! the first derivative of the interpolating function at points 1 and n, y2(1) = -0.5
! this routine returns an array y2(1:n) of length n which contains the u(1) = (3./(x(2)-x(1)))*((y(2)-y(1))/(x(2)-x(1))-yp1)
! second derivatives of the interpolating function at the tabulated endif
! points x_i. If yp1 and ypn are equal 1.d30 or larger, the routine do i = 2,n-1
! is signalled to set the corresponding boundary conditions for a sig = (x(i)-x(i-1))/(x(i+1)-x(i-1))
! natural spline, with zero second derivative on that boundary. p = sig*y2(i-1)+2.
! (c) modified from Numerical recipes y2(i) = (sig-1.)/p
!----------------------------------------------------------------------- u(i) = (6.*((y(i+1)-y(i))/(x(i+1)-x(i))-(y(i)-y(i-1)) &
implicit none & /(x(i)-x(i-1)))/(x(i+1)-x(i-1))-sig*u(i-1))/p
integer :: n,i,k enddo
integer, parameter :: idouble = kind(1.0d0) if (ypn.gt..99e30) then
integer, parameter :: isingle = kind(1.0) qn = 0.
real(idouble), dimension(n), intent(in) :: x,y un = 0.
real(idouble), dimension(n), intent(out) :: y2 else
real(idouble), dimension(n) :: u qn = 0.5
real(idouble), intent(in) :: yp1,ypn un = (3./(x(n)-x(n-1)))*(ypn-(y(n)-y(n-1))/(x(n)-x(n-1)))
real(idouble) :: p,qn,sig,un endif
y2(n) = (un-qn*u(n-1))/(qn*y2(n-1)+1.)
do k = n-1,1,-1
y2(k) = y2(k)*y2(k+1)+u(k)
enddo
return
end subroutine spline
1D Cubic Splines exercise
SUBROUTINE splint(xa, ya, y2a, n, x, y)
! USE nrtype
splines1d.f90 !
! Given the arrays xa(1:n) and ya(1:n) of length n, which tabulate a function
spline.f90 ! (with the xa(i) in order), and given the array y2a(1:n), which is the output
! from the subroutine spline, and given a value of x, this routine returns a
splint.f90 ! cubic spline interpolated value y.
! Adapted from Numerical Recipes in FORTRAN 77
!
IMPLICIT NONE
INTEGER, PARAMETER :: DP = KIND(1.0D0)
INTEGER :: n
REAL(DP) :: x, y, xa(n), y2a(n), ya(n)
INTEGER :: k, khi, klo
REAL(DP) :: a, b, h
klo=1
khi=n
1 if (khi-klo.gt.1) then
k=(khi+klo)/2
if (xa(k).gt.x) then
khi=k
else
klo=k
endif
goto 1
endif
h=xa(khi)-xa(klo)
if (h.eq.0.) then
write(*,*) 'bad xa input in splint'
stop
endif
a=(xa(khi)-x)/h
b=(x-xa(klo))/h
y=a*ya(klo)+b*ya(khi)+((a**3-a)*y2a(klo)+(b**3-b)*y2a(khi))*(h**2)/6.
return
END SUBROUTINE splint
1D Cubic Splines example
splines1d.f90
spline.f90
splint.f90

splines1d.in
compile_splines1d

./splines1d.x

splines1d.out

Choosing the knots properly is very important !


1D Cubic Splines example
splines1d.f90
spline.f90
splint.f90
Utilizando las rutinas spline.f90 y splint.f90, interpolar datos de
splines1d.in 1
f ( x )=
compile_splines1d 1+12 x 2
tomados en el intervalo [-1, 1] (equiespaciados)
./splines1d.x
- Comparar los resultados con los de la interpolación polinomial de
splines1d.out
grado 10 ya realizada utilizando la misma grilla de datos

- Analizar el efecto de posibles condiciones extra (por ej. derivadas


primera o segunda en los extremos) y con el número de datos
Splines in 2D
Bilinear Splines is very simple !
… but not smooth enough for applications
that require derivatives of F(x,y) (e.g. MD)

Cubic Splines
How to proceed in 2D ?

f(xi,yj+1) f(xi+1,yj+1) {(xi;yj); f(xi;yj)}i=1,...m;j=1,...n


yj+1
ONLY ONCE
y 1st) Construction step for j=1,…,n → f’’x(xi,yj)
~ n times order m = order n×m
f(xi,yj) f(xi+1,yj)
yj 2nd) Locate x and y → i,j ~ log n + log m

x xi+1 AS MANY TIMES AS NEEDED


x
i
3rd) Evaluation step in x for j=1,…,n → f(x,yj) ~n
N (>> n×m) interpolations: 4th) Construction step → fy’’(x,yj) ~m
is a process ~ (n+m) × N
5th) Evaluation step in y → f(x,y) ~1
2D Cubic Splines exercise
program splines2d
splines2d.f90 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
implicit none
integer :: i,j,ndatx,ndaty,ncalcx,ncalcy
No input file real(8) :: fun
real(8), allocatable :: x(:),y(:),f(:,:),f2x(:,:),f_int_x(:),f2_int_x(:)
real(8) :: yp1,ypn
compile_splines2d real(8) :: x_int,y_int,f_int
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
ndatx=4 ! number of knots in the x direction
./splines2d.x allocate(x(ndatx))
do i=1,ndatx
x(i)=real(i-1)/real(ndatx-1) ! gererate the x coordinates of the knots (regular grid)
splines2d.out enddo

ndaty=4 ! number of knots in the y direction


allocate(y(ndaty))
do j=1,ndaty
y(j)=real(j-1)/real(ndaty-1) ! gererate the y coordinates of the knots (regular grid)
enddo

allocate(f(ndatx,ndaty),f2x(ndatx,ndaty),f_int_x(ndaty),f2_int_x(ndaty))

do i=1,ndatx
do j=1,ndaty
f(i,j)=fun(x(i),y(j)) ! compute and store the function in the knots
enddo
enddo

yp1=1.e30 ! we choose natural splines at the beginning of the interval


ypn=1.e30 ! we choose natural splines at the end of the interval

do j=1,ndaty
call spline(x, f(:,j), ndatx, yp1, ypn, f2x(:,j)) ! construction (ndaty times)
enddo

2D Cubic Splines exercise
splines2d.f90

No input file ncalcx=3 ! number of x values to evaluate the interpolation function


ncalcy=101 ! number of y values to evaluate the interpolation function
compile_splines2d open(10,file='interp2d.out',status='unknown') ! opening the output file
do i=1,ncalcx
x_int=x(1)+(x(ndatx)-x(1))*real(i-1)/real(ncalcx-1) ! x for the points to evaluate the splines 2d
./splines2d.x do j=1,ndaty
call splint(x, f(:,j), f2x(:,j), ndatx, x_int, f_int_x(j)) ! evaluation (ndaty times per x_int,y_int point)
enddo
splines2d.out call spline(y, f_int_x, ndaty, yp1, ypn, f2_int_x) ! construction (1 time per x_int,y_int point)
do j=1,ncalcy
y_int=y(1)+(y(ndaty)-y(1))*real(j-1)/real(ncalcy-1) ! y for the points to evaluate the splines 2d
call splint(y, f_int_x, f2_int_x, ndaty, y_int, f_int) ! evaluation (1 time per x_int,y_int point)
write(10,104) x_int,y_int,fun(x_int,y_int),f_int ! write the exact and splines results
enddo
write(10,*)' '
enddo
close(10)
deallocate(x,y,f,f2x,f_int_x,f2_int_x)
104 format(4f15.8)
end program splines2d

function fun(x,y)
implicit none
real (8) :: x,y,fun
fun=exp(-4._8*(x**2+y**2))
end function fun
y
2D Cubic Splines example
4x4=16 knots
1

0
0 1 x
Gaussian function
centered at the origin
y
2D Cubic Splines example
4x4=16 knots
1

Using grids that respect the symmetry of


the function we want to represent might be
better than increasing the density of data

0
0 1 x
7x7=49 knots Gaussian function
centered at the origin
y

x
How much can we increase the number of variables ?
N atoms → 3N coordinates E.g. N=2 atoms (H2 in an external potential)

→ n3N data !! 7 points per coordinate


n data per coordinate

76=117649 Ab Initio points


If 1 point ~ 1/2 hour → 6,7 years

Coupling between coordinates: what does it mean ?


We say that there is a strong coupling between two coordinates (x,y) when we deal with a
function f(x,y) if the y-dependence of f change a lot with the value of x and vice versa

If there is now coupling between the 3N coordinates we might need only


n values per coordinate (irrespective of the value of all the other 3N-1 coordinates), that is
~ nx3N might be enough ! (instead of n3N)
For n=7 and N=2 → 42 points instead of 117649 !!!

Is this possible ?

Some coordinates can be uncoupled one from the other (symmetry properties)
How much can we increase the number of variables ?
Coupling between coordinates: what does it mean ?
We say that there is a strong coupling between two coordinates (x,y) when we deal with a
function f(x,y) if the y-dependence of f change a lot with the value of x and vice versa

4 points is ENOUGH !

If we set f’(0)=0

Is this possible ?
Some coordinates can be uncoupled one from the other due to a symmetry property !

But the coordinates convenient for two symmetry properties of the potential are not the same !
FIN NOTAS DE CLASE

Tema: Ajuste de datos


Fitting e interpolación

También podría gustarte