SlideShare a Scribd company logo
1 of 7
Año de la Diversificación Productiva y del Fortalecimiento de la
Educación
UNIVERSIDAD NACIONAL
DEL CALLAO
FACULTAD DE CIENCIAS
NATURALES Y MATEMÁTICA
FÍSICA TEÓRICA COMPUTACIONAL II
“ECUACIÓN DIFERENCIAL HIPERBÓLICA USANDO
FORTRAN 90, SCILAB 5.5 Y MATLAB.”
MARCO ANTONIO ALPACA CHAMBA
ESCUELA PROFESIONAL DE: FÍSICA
𝝏 𝟐
𝒖
𝝏𝒙 𝟐
=
𝝏 𝟐
𝒖
𝝏𝒕 𝟐
PROGRAM
IMPLICIT NONE
REAL, INTEGER…
30 -05-2015
Considerar la siguiente ecuación hiperbólica con condiciones iniciales y de frontera:
𝝏 𝟐
𝒖
𝝏𝒙 𝟐
=
𝝏 𝟐
𝒖
𝝏𝒕 𝟐
𝒖( 𝒙, 𝒕) = 𝒖( 𝟏, 𝒕) = 𝟎 , 𝒙 ∈ [ 𝟎, 𝟏]
𝒖( 𝒙, 𝟎) = 𝒔𝒊𝒏( 𝝅𝒙) + 𝟎. 𝟓𝒔𝒊𝒏( 𝟑𝝅𝒙)
𝒖′( 𝒙, 𝟎) = 𝟎
Hallar las soluciones usando FORTRAN, SCILAB Y MATLAB
SOLUCIÓN:
USANDO FORTRAN TENEMOS:
PROGRAM HYPERBOLIC
PARAMETER (IDM=100)
DIMENSION X(IDM),T(IDM),U(IDM,IDM)
REAL GAM,HT,HX,NT,NX,PI
OPEN(UNIT=11,FILE='HIPERBÓLICA.TXT',STATUS='UNKNOWN',ACTION='WRITE')
PRINT*,''
PRINT*,
'====================================================================='
PRINT*,' HYPERBOLIC PARTIAL DIFFERENTIAL EQUATION'
PRINT*,'==================================================================
===='
PRINT*,''
PRINT*, 'INGRESAR EL RANGO INFERIOR DE LA VARIABLE X (X=0):'
READ(5,*) AX
PRINT*, 'INGRESAR EL RANGO SUPERIOR DE LA VARIABLE X (X=1):'
READ*, BX
PRINT*, 'INGRESAR EL NUMBER DE SUBINTERVALOS DE X (N=10):'
READ*, NX
PRINT*,'INGRESAR EL RANGO INFERIOR DE LA VARIABLE T (T=0):'
READ*,AT
PRINT*, 'INGRESAR EL RANGO SUPERIOR DE LA VARIABLE T (T=1):'
READ*, BT
PRINT*, 'INGRESAR EL NUMBER DE SUBINTERVALOS DE T (N= 20):'
READ*, NT
PRINT*,''
PRINT*,('*',I=1,79)
PRINT '(5X,"RESULTADOS COMPUTACIONALES")'
PRINT*,('*',I=1,79)
PRINT*,''
PI = 4.0*ATAN(1.0)
HX=(BX-AX)/NX
HT=(BT-AT)/NT
DO I=1,NX+1
X(I)=(I-1)*HX
ENDDO
DO J=1,NT+1
T(J)=(J-1)*HT
ENDDO
DO I=2,NX
X(I)=(I-1)*HX
U(I,1)=F(X(I))
U(I,2)=U(I,1)+HT*G1(X(I))
ENDDO
DO J=1,NT+1
U(1,J)=0
U(NX+1,J)=0
ENDDO
A=1
GAM=(A**2)*(HT**2)/(HX**2)
WRITE(11,7)AT,(AT+(L1-1)*HT,L1=1,NT+1)
!PRINT'(2X,F5.2,21F5.2)',AT,(AT+(L1-1)*HT,L1=1,NT+1)
DO J=2,NT
DO I=2,NX
U(I,J+1)=-U(I,J-1)+GAM*U(I-1,J)+(2-2*GAM)*U(I,J)+GAM*U(I+1,J)
ENDDO
ENDDO
7 FORMAT (2X,F5.2,21(3X,F5.2))
DO I=1,NX+1
WRITE(11,9)AX,(U(I,J),J=1,NT+1)
PRINT '(2X,F5.2,21F8.4)',AX,(U(I,J),J=1,NT+1)
AX=AX+HX
ENDDO
9 FORMAT(2X,F5.2,21F8.4)
PRINT*,''
STOP
CONTAINS
FUNCTION F(X)
REAL X,F
F=SIN(PI*X)+0.5*SIN(3*PI*X)
RETURN
END FUNCTION
FUNCTION G1(Y)
REAL Y,G1
G1=0+0*Y
RETURN
END FUNCTION
END
USANDO SCILAB TENEMOS:
function y=fi(x)
y=sin(%pi*x)+0.5*sin(3*%pi*x);
endfunction
function y=psi(x)
y=0
endfunction
function [u, x, t]=ggg(N, K, L, T, a)
h=L/N;
delta=T/K;
for i=1:N+1
x(i)=(i-1)*h;
end
for i=2:N
x(i)=(i-1)*h;
u(i,1)=fi(x(i));
u(i,2)=u(i,1)+delta*psi(x(i));
end
for j=1:K+1
t(j)=(j-1)*delta;
end
for j=1:K+1
u(1,j)=0;
u(N+1,j)=0;
end
gam=a^2*delta^2/h^2;
for j=2:K
for i=2:N
u(i,j+1)=-u(i,j-1)+gam*u(i-1,j)+(2-2*gam)*...
u(i,j)+gam*u(i+1,j);
end
end
endfunction
a=1;
[u,x,t]=ggg(10,20,1,1,a);
surf(x,t,u');
xlabel('X','fontsize',4);
ylabel('T','fontsize',4);
zlabel('U','fontsize',4);
title('Solución de una ecuación hiperbólica','fontsize',6);
USANDO MATLAB TENEMOS:
PP:
clear
clc
fi=@(x)sin(pi*x)+0.5*sin(3*pi*x);
psi=@(t)0;
a=1;
[u,x,t]=ggg(fi,psi,10,20,1,1,a);
figure('color',[1,1,1]);
surf(x,t,u');
xlabel('X');
ylabel('T');
zlabel('U');
title('Solución de una ecuación hiperbólica');
PS:
function [u, x, t]=ggg(fi,psi,N, K, L, T, a)
h=L/N;
delta=T/K;
for i=1:N+1
x(i)=(i-1)*h;
end
for i=2:N
x(i)=(i-1)*h;
u(i,1)=fi(x(i));
u(i,2)=u(i,1)+delta*psi(x(i));
end
for j=1:K+1
t(j)=(j-1)*delta;
end
for j=1:K+1
u(1,j)=0;
u(N+1,j)=0;
end
gam=a^2*delta^2/h^2;
for j=2:K
for i=2:N
u(i,j+1)=-u(i,j-1)+gam*u(i-1,j)+(2-2*gam)*...
u(i,j)+gam*u(i+1,j);
end
end
end

More Related Content

More from Marco Antonio

DIVISIÓN POLINÓMICA
DIVISIÓN POLINÓMICADIVISIÓN POLINÓMICA
DIVISIÓN POLINÓMICAMarco Antonio
 
Interpolación aritmética
Interpolación aritméticaInterpolación aritmética
Interpolación aritméticaMarco Antonio
 
PREFIJOS DEL SISTEMA MÉTRICO
PREFIJOS DEL SISTEMA MÉTRICOPREFIJOS DEL SISTEMA MÉTRICO
PREFIJOS DEL SISTEMA MÉTRICOMarco Antonio
 
EXAMEN DE SUBSANACIÓN DE ÁLGEBRA
EXAMEN DE SUBSANACIÓN DE ÁLGEBRAEXAMEN DE SUBSANACIÓN DE ÁLGEBRA
EXAMEN DE SUBSANACIÓN DE ÁLGEBRAMarco Antonio
 
Prefijos del sistema internacional
Prefijos del sistema internacionalPrefijos del sistema internacional
Prefijos del sistema internacionalMarco Antonio
 
monthly exam of algebra
monthly exam of algebramonthly exam of algebra
monthly exam of algebraMarco Antonio
 
Problemas resueltos de Factorización
Problemas resueltos de FactorizaciónProblemas resueltos de Factorización
Problemas resueltos de FactorizaciónMarco Antonio
 
solucionario del examen de álgebra
solucionario del examen de álgebrasolucionario del examen de álgebra
solucionario del examen de álgebraMarco Antonio
 
Examen Bimestral de Aritmética 5° de primaria
Examen Bimestral de Aritmética 5° de primariaExamen Bimestral de Aritmética 5° de primaria
Examen Bimestral de Aritmética 5° de primariaMarco Antonio
 
Examen Bimestral de Aritmética 6° de primaria
Examen Bimestral de Aritmética 6° de primariaExamen Bimestral de Aritmética 6° de primaria
Examen Bimestral de Aritmética 6° de primariaMarco Antonio
 
Brevísima historia de Arquímedes
Brevísima historia de ArquímedesBrevísima historia de Arquímedes
Brevísima historia de ArquímedesMarco Antonio
 
El principio de Le Chatelier
El principio de Le Chatelier El principio de Le Chatelier
El principio de Le Chatelier Marco Antonio
 
COMPARACIÓN DE LOS MÉTODOS ITERATIVOS DE RUNGE KUTTA 2 ORDEN CON RUNGR KUTTA ...
COMPARACIÓN DE LOS MÉTODOS ITERATIVOS DE RUNGE KUTTA 2 ORDEN CON RUNGR KUTTA ...COMPARACIÓN DE LOS MÉTODOS ITERATIVOS DE RUNGE KUTTA 2 ORDEN CON RUNGR KUTTA ...
COMPARACIÓN DE LOS MÉTODOS ITERATIVOS DE RUNGE KUTTA 2 ORDEN CON RUNGR KUTTA ...Marco Antonio
 
MÉTODO DE RUNGE KUTTA DE 4 ORDEN PARA RESOLVER UNA ECUACIÓN DIFERENCIAL DE SE...
MÉTODO DE RUNGE KUTTA DE 4 ORDEN PARA RESOLVER UNA ECUACIÓN DIFERENCIAL DE SE...MÉTODO DE RUNGE KUTTA DE 4 ORDEN PARA RESOLVER UNA ECUACIÓN DIFERENCIAL DE SE...
MÉTODO DE RUNGE KUTTA DE 4 ORDEN PARA RESOLVER UNA ECUACIÓN DIFERENCIAL DE SE...Marco Antonio
 
COMPARACIÓN DE LOS MÉTODOS ITERATIVOS ADAMAS-BALTHOR-MOULT PREDICTOR CORRECTO...
COMPARACIÓN DE LOS MÉTODOS ITERATIVOS ADAMAS-BALTHOR-MOULT PREDICTOR CORRECTO...COMPARACIÓN DE LOS MÉTODOS ITERATIVOS ADAMAS-BALTHOR-MOULT PREDICTOR CORRECTO...
COMPARACIÓN DE LOS MÉTODOS ITERATIVOS ADAMAS-BALTHOR-MOULT PREDICTOR CORRECTO...Marco Antonio
 
MÉTODO ITERATIVO DE GAUSS_SEIDEL USANDO FORTRAN 90, MATLAB Y SCILAB
MÉTODO ITERATIVO DE GAUSS_SEIDEL USANDO FORTRAN 90, MATLAB Y SCILABMÉTODO ITERATIVO DE GAUSS_SEIDEL USANDO FORTRAN 90, MATLAB Y SCILAB
MÉTODO ITERATIVO DE GAUSS_SEIDEL USANDO FORTRAN 90, MATLAB Y SCILABMarco Antonio
 
Sesion multiplexores y demultiplexores
Sesion  multiplexores y demultiplexores Sesion  multiplexores y demultiplexores
Sesion multiplexores y demultiplexores Marco Antonio
 

More from Marco Antonio (20)

DIVISIÓN POLINÓMICA
DIVISIÓN POLINÓMICADIVISIÓN POLINÓMICA
DIVISIÓN POLINÓMICA
 
Interpolación aritmética
Interpolación aritméticaInterpolación aritmética
Interpolación aritmética
 
PREFIJOS DEL SISTEMA MÉTRICO
PREFIJOS DEL SISTEMA MÉTRICOPREFIJOS DEL SISTEMA MÉTRICO
PREFIJOS DEL SISTEMA MÉTRICO
 
EXAMEN DE SUBSANACIÓN DE ÁLGEBRA
EXAMEN DE SUBSANACIÓN DE ÁLGEBRAEXAMEN DE SUBSANACIÓN DE ÁLGEBRA
EXAMEN DE SUBSANACIÓN DE ÁLGEBRA
 
Prefijos del sistema internacional
Prefijos del sistema internacionalPrefijos del sistema internacional
Prefijos del sistema internacional
 
monthly exam of algebra
monthly exam of algebramonthly exam of algebra
monthly exam of algebra
 
Factorización
FactorizaciónFactorización
Factorización
 
Problemas resueltos de Factorización
Problemas resueltos de FactorizaciónProblemas resueltos de Factorización
Problemas resueltos de Factorización
 
solucionario del examen de álgebra
solucionario del examen de álgebrasolucionario del examen de álgebra
solucionario del examen de álgebra
 
Examen Bimestral de Aritmética 5° de primaria
Examen Bimestral de Aritmética 5° de primariaExamen Bimestral de Aritmética 5° de primaria
Examen Bimestral de Aritmética 5° de primaria
 
Examen Bimestral de Aritmética 6° de primaria
Examen Bimestral de Aritmética 6° de primariaExamen Bimestral de Aritmética 6° de primaria
Examen Bimestral de Aritmética 6° de primaria
 
Brevísima historia de Arquímedes
Brevísima historia de ArquímedesBrevísima historia de Arquímedes
Brevísima historia de Arquímedes
 
El principio de Le Chatelier
El principio de Le Chatelier El principio de Le Chatelier
El principio de Le Chatelier
 
Arquímedes
ArquímedesArquímedes
Arquímedes
 
COMPARACIÓN DE LOS MÉTODOS ITERATIVOS DE RUNGE KUTTA 2 ORDEN CON RUNGR KUTTA ...
COMPARACIÓN DE LOS MÉTODOS ITERATIVOS DE RUNGE KUTTA 2 ORDEN CON RUNGR KUTTA ...COMPARACIÓN DE LOS MÉTODOS ITERATIVOS DE RUNGE KUTTA 2 ORDEN CON RUNGR KUTTA ...
COMPARACIÓN DE LOS MÉTODOS ITERATIVOS DE RUNGE KUTTA 2 ORDEN CON RUNGR KUTTA ...
 
MÉTODO DE RUNGE KUTTA DE 4 ORDEN PARA RESOLVER UNA ECUACIÓN DIFERENCIAL DE SE...
MÉTODO DE RUNGE KUTTA DE 4 ORDEN PARA RESOLVER UNA ECUACIÓN DIFERENCIAL DE SE...MÉTODO DE RUNGE KUTTA DE 4 ORDEN PARA RESOLVER UNA ECUACIÓN DIFERENCIAL DE SE...
MÉTODO DE RUNGE KUTTA DE 4 ORDEN PARA RESOLVER UNA ECUACIÓN DIFERENCIAL DE SE...
 
COMPARACIÓN DE LOS MÉTODOS ITERATIVOS ADAMAS-BALTHOR-MOULT PREDICTOR CORRECTO...
COMPARACIÓN DE LOS MÉTODOS ITERATIVOS ADAMAS-BALTHOR-MOULT PREDICTOR CORRECTO...COMPARACIÓN DE LOS MÉTODOS ITERATIVOS ADAMAS-BALTHOR-MOULT PREDICTOR CORRECTO...
COMPARACIÓN DE LOS MÉTODOS ITERATIVOS ADAMAS-BALTHOR-MOULT PREDICTOR CORRECTO...
 
MÉTODO ITERATIVO DE GAUSS_SEIDEL USANDO FORTRAN 90, MATLAB Y SCILAB
MÉTODO ITERATIVO DE GAUSS_SEIDEL USANDO FORTRAN 90, MATLAB Y SCILABMÉTODO ITERATIVO DE GAUSS_SEIDEL USANDO FORTRAN 90, MATLAB Y SCILAB
MÉTODO ITERATIVO DE GAUSS_SEIDEL USANDO FORTRAN 90, MATLAB Y SCILAB
 
Sesion multiplexores y demultiplexores
Sesion  multiplexores y demultiplexores Sesion  multiplexores y demultiplexores
Sesion multiplexores y demultiplexores
 
Sesion flips flops
Sesion  flips flopsSesion  flips flops
Sesion flips flops
 

Recently uploaded

Framing an Appropriate Research Question 6b9b26d93da94caf993c038d9efcdedb.pdf
Framing an Appropriate Research Question 6b9b26d93da94caf993c038d9efcdedb.pdfFraming an Appropriate Research Question 6b9b26d93da94caf993c038d9efcdedb.pdf
Framing an Appropriate Research Question 6b9b26d93da94caf993c038d9efcdedb.pdfUjwalaBharambe
 
Final demo Grade 9 for demo Plan dessert.pptx
Final demo Grade 9 for demo Plan dessert.pptxFinal demo Grade 9 for demo Plan dessert.pptx
Final demo Grade 9 for demo Plan dessert.pptxAvyJaneVismanos
 
KSHARA STURA .pptx---KSHARA KARMA THERAPY (CAUSTIC THERAPY)————IMP.OF KSHARA ...
KSHARA STURA .pptx---KSHARA KARMA THERAPY (CAUSTIC THERAPY)————IMP.OF KSHARA ...KSHARA STURA .pptx---KSHARA KARMA THERAPY (CAUSTIC THERAPY)————IMP.OF KSHARA ...
KSHARA STURA .pptx---KSHARA KARMA THERAPY (CAUSTIC THERAPY)————IMP.OF KSHARA ...M56BOOKSTORE PRODUCT/SERVICE
 
Roles & Responsibilities in Pharmacovigilance
Roles & Responsibilities in PharmacovigilanceRoles & Responsibilities in Pharmacovigilance
Roles & Responsibilities in PharmacovigilanceSamikshaHamane
 
CARE OF CHILD IN INCUBATOR..........pptx
CARE OF CHILD IN INCUBATOR..........pptxCARE OF CHILD IN INCUBATOR..........pptx
CARE OF CHILD IN INCUBATOR..........pptxGaneshChakor2
 
call girls in Kamla Market (DELHI) 🔝 >༒9953330565🔝 genuine Escort Service 🔝✔️✔️
call girls in Kamla Market (DELHI) 🔝 >༒9953330565🔝 genuine Escort Service 🔝✔️✔️call girls in Kamla Market (DELHI) 🔝 >༒9953330565🔝 genuine Escort Service 🔝✔️✔️
call girls in Kamla Market (DELHI) 🔝 >༒9953330565🔝 genuine Escort Service 🔝✔️✔️9953056974 Low Rate Call Girls In Saket, Delhi NCR
 
Biting mechanism of poisonous snakes.pdf
Biting mechanism of poisonous snakes.pdfBiting mechanism of poisonous snakes.pdf
Biting mechanism of poisonous snakes.pdfadityarao40181
 
ECONOMIC CONTEXT - LONG FORM TV DRAMA - PPT
ECONOMIC CONTEXT - LONG FORM TV DRAMA - PPTECONOMIC CONTEXT - LONG FORM TV DRAMA - PPT
ECONOMIC CONTEXT - LONG FORM TV DRAMA - PPTiammrhaywood
 
“Oh GOSH! Reflecting on Hackteria's Collaborative Practices in a Global Do-It...
“Oh GOSH! Reflecting on Hackteria's Collaborative Practices in a Global Do-It...“Oh GOSH! Reflecting on Hackteria's Collaborative Practices in a Global Do-It...
“Oh GOSH! Reflecting on Hackteria's Collaborative Practices in a Global Do-It...Marc Dusseiller Dusjagr
 
Interactive Powerpoint_How to Master effective communication
Interactive Powerpoint_How to Master effective communicationInteractive Powerpoint_How to Master effective communication
Interactive Powerpoint_How to Master effective communicationnomboosow
 
भारत-रोम व्यापार.pptx, Indo-Roman Trade,
भारत-रोम व्यापार.pptx, Indo-Roman Trade,भारत-रोम व्यापार.pptx, Indo-Roman Trade,
भारत-रोम व्यापार.pptx, Indo-Roman Trade,Virag Sontakke
 
Introduction to ArtificiaI Intelligence in Higher Education
Introduction to ArtificiaI Intelligence in Higher EducationIntroduction to ArtificiaI Intelligence in Higher Education
Introduction to ArtificiaI Intelligence in Higher Educationpboyjonauth
 
DATA STRUCTURE AND ALGORITHM for beginners
DATA STRUCTURE AND ALGORITHM for beginnersDATA STRUCTURE AND ALGORITHM for beginners
DATA STRUCTURE AND ALGORITHM for beginnersSabitha Banu
 
Computed Fields and api Depends in the Odoo 17
Computed Fields and api Depends in the Odoo 17Computed Fields and api Depends in the Odoo 17
Computed Fields and api Depends in the Odoo 17Celine George
 
How to Make a Pirate ship Primary Education.pptx
How to Make a Pirate ship Primary Education.pptxHow to Make a Pirate ship Primary Education.pptx
How to Make a Pirate ship Primary Education.pptxmanuelaromero2013
 
History Class XII Ch. 3 Kinship, Caste and Class (1).pptx
History Class XII Ch. 3 Kinship, Caste and Class (1).pptxHistory Class XII Ch. 3 Kinship, Caste and Class (1).pptx
History Class XII Ch. 3 Kinship, Caste and Class (1).pptxsocialsciencegdgrohi
 
Crayon Activity Handout For the Crayon A
Crayon Activity Handout For the Crayon ACrayon Activity Handout For the Crayon A
Crayon Activity Handout For the Crayon AUnboundStockton
 
MARGINALIZATION (Different learners in Marginalized Group
MARGINALIZATION (Different learners in Marginalized GroupMARGINALIZATION (Different learners in Marginalized Group
MARGINALIZATION (Different learners in Marginalized GroupJonathanParaisoCruz
 
Proudly South Africa powerpoint Thorisha.pptx
Proudly South Africa powerpoint Thorisha.pptxProudly South Africa powerpoint Thorisha.pptx
Proudly South Africa powerpoint Thorisha.pptxthorishapillay1
 

Recently uploaded (20)

Model Call Girl in Tilak Nagar Delhi reach out to us at 🔝9953056974🔝
Model Call Girl in Tilak Nagar Delhi reach out to us at 🔝9953056974🔝Model Call Girl in Tilak Nagar Delhi reach out to us at 🔝9953056974🔝
Model Call Girl in Tilak Nagar Delhi reach out to us at 🔝9953056974🔝
 
Framing an Appropriate Research Question 6b9b26d93da94caf993c038d9efcdedb.pdf
Framing an Appropriate Research Question 6b9b26d93da94caf993c038d9efcdedb.pdfFraming an Appropriate Research Question 6b9b26d93da94caf993c038d9efcdedb.pdf
Framing an Appropriate Research Question 6b9b26d93da94caf993c038d9efcdedb.pdf
 
Final demo Grade 9 for demo Plan dessert.pptx
Final demo Grade 9 for demo Plan dessert.pptxFinal demo Grade 9 for demo Plan dessert.pptx
Final demo Grade 9 for demo Plan dessert.pptx
 
KSHARA STURA .pptx---KSHARA KARMA THERAPY (CAUSTIC THERAPY)————IMP.OF KSHARA ...
KSHARA STURA .pptx---KSHARA KARMA THERAPY (CAUSTIC THERAPY)————IMP.OF KSHARA ...KSHARA STURA .pptx---KSHARA KARMA THERAPY (CAUSTIC THERAPY)————IMP.OF KSHARA ...
KSHARA STURA .pptx---KSHARA KARMA THERAPY (CAUSTIC THERAPY)————IMP.OF KSHARA ...
 
Roles & Responsibilities in Pharmacovigilance
Roles & Responsibilities in PharmacovigilanceRoles & Responsibilities in Pharmacovigilance
Roles & Responsibilities in Pharmacovigilance
 
CARE OF CHILD IN INCUBATOR..........pptx
CARE OF CHILD IN INCUBATOR..........pptxCARE OF CHILD IN INCUBATOR..........pptx
CARE OF CHILD IN INCUBATOR..........pptx
 
call girls in Kamla Market (DELHI) 🔝 >༒9953330565🔝 genuine Escort Service 🔝✔️✔️
call girls in Kamla Market (DELHI) 🔝 >༒9953330565🔝 genuine Escort Service 🔝✔️✔️call girls in Kamla Market (DELHI) 🔝 >༒9953330565🔝 genuine Escort Service 🔝✔️✔️
call girls in Kamla Market (DELHI) 🔝 >༒9953330565🔝 genuine Escort Service 🔝✔️✔️
 
Biting mechanism of poisonous snakes.pdf
Biting mechanism of poisonous snakes.pdfBiting mechanism of poisonous snakes.pdf
Biting mechanism of poisonous snakes.pdf
 
ECONOMIC CONTEXT - LONG FORM TV DRAMA - PPT
ECONOMIC CONTEXT - LONG FORM TV DRAMA - PPTECONOMIC CONTEXT - LONG FORM TV DRAMA - PPT
ECONOMIC CONTEXT - LONG FORM TV DRAMA - PPT
 
“Oh GOSH! Reflecting on Hackteria's Collaborative Practices in a Global Do-It...
“Oh GOSH! Reflecting on Hackteria's Collaborative Practices in a Global Do-It...“Oh GOSH! Reflecting on Hackteria's Collaborative Practices in a Global Do-It...
“Oh GOSH! Reflecting on Hackteria's Collaborative Practices in a Global Do-It...
 
Interactive Powerpoint_How to Master effective communication
Interactive Powerpoint_How to Master effective communicationInteractive Powerpoint_How to Master effective communication
Interactive Powerpoint_How to Master effective communication
 
भारत-रोम व्यापार.pptx, Indo-Roman Trade,
भारत-रोम व्यापार.pptx, Indo-Roman Trade,भारत-रोम व्यापार.pptx, Indo-Roman Trade,
भारत-रोम व्यापार.pptx, Indo-Roman Trade,
 
Introduction to ArtificiaI Intelligence in Higher Education
Introduction to ArtificiaI Intelligence in Higher EducationIntroduction to ArtificiaI Intelligence in Higher Education
Introduction to ArtificiaI Intelligence in Higher Education
 
DATA STRUCTURE AND ALGORITHM for beginners
DATA STRUCTURE AND ALGORITHM for beginnersDATA STRUCTURE AND ALGORITHM for beginners
DATA STRUCTURE AND ALGORITHM for beginners
 
Computed Fields and api Depends in the Odoo 17
Computed Fields and api Depends in the Odoo 17Computed Fields and api Depends in the Odoo 17
Computed Fields and api Depends in the Odoo 17
 
How to Make a Pirate ship Primary Education.pptx
How to Make a Pirate ship Primary Education.pptxHow to Make a Pirate ship Primary Education.pptx
How to Make a Pirate ship Primary Education.pptx
 
History Class XII Ch. 3 Kinship, Caste and Class (1).pptx
History Class XII Ch. 3 Kinship, Caste and Class (1).pptxHistory Class XII Ch. 3 Kinship, Caste and Class (1).pptx
History Class XII Ch. 3 Kinship, Caste and Class (1).pptx
 
Crayon Activity Handout For the Crayon A
Crayon Activity Handout For the Crayon ACrayon Activity Handout For the Crayon A
Crayon Activity Handout For the Crayon A
 
MARGINALIZATION (Different learners in Marginalized Group
MARGINALIZATION (Different learners in Marginalized GroupMARGINALIZATION (Different learners in Marginalized Group
MARGINALIZATION (Different learners in Marginalized Group
 
Proudly South Africa powerpoint Thorisha.pptx
Proudly South Africa powerpoint Thorisha.pptxProudly South Africa powerpoint Thorisha.pptx
Proudly South Africa powerpoint Thorisha.pptx
 

Ecuación Diferencial Hiperbólica usando fortran, matlab y scilab.

  • 1. Año de la Diversificación Productiva y del Fortalecimiento de la Educación UNIVERSIDAD NACIONAL DEL CALLAO FACULTAD DE CIENCIAS NATURALES Y MATEMÁTICA FÍSICA TEÓRICA COMPUTACIONAL II “ECUACIÓN DIFERENCIAL HIPERBÓLICA USANDO FORTRAN 90, SCILAB 5.5 Y MATLAB.” MARCO ANTONIO ALPACA CHAMBA ESCUELA PROFESIONAL DE: FÍSICA 𝝏 𝟐 𝒖 𝝏𝒙 𝟐 = 𝝏 𝟐 𝒖 𝝏𝒕 𝟐 PROGRAM IMPLICIT NONE REAL, INTEGER… 30 -05-2015
  • 2. Considerar la siguiente ecuación hiperbólica con condiciones iniciales y de frontera: 𝝏 𝟐 𝒖 𝝏𝒙 𝟐 = 𝝏 𝟐 𝒖 𝝏𝒕 𝟐 𝒖( 𝒙, 𝒕) = 𝒖( 𝟏, 𝒕) = 𝟎 , 𝒙 ∈ [ 𝟎, 𝟏] 𝒖( 𝒙, 𝟎) = 𝒔𝒊𝒏( 𝝅𝒙) + 𝟎. 𝟓𝒔𝒊𝒏( 𝟑𝝅𝒙) 𝒖′( 𝒙, 𝟎) = 𝟎 Hallar las soluciones usando FORTRAN, SCILAB Y MATLAB SOLUCIÓN: USANDO FORTRAN TENEMOS: PROGRAM HYPERBOLIC PARAMETER (IDM=100) DIMENSION X(IDM),T(IDM),U(IDM,IDM) REAL GAM,HT,HX,NT,NX,PI OPEN(UNIT=11,FILE='HIPERBÓLICA.TXT',STATUS='UNKNOWN',ACTION='WRITE') PRINT*,'' PRINT*, '=====================================================================' PRINT*,' HYPERBOLIC PARTIAL DIFFERENTIAL EQUATION' PRINT*,'================================================================== ====' PRINT*,'' PRINT*, 'INGRESAR EL RANGO INFERIOR DE LA VARIABLE X (X=0):' READ(5,*) AX PRINT*, 'INGRESAR EL RANGO SUPERIOR DE LA VARIABLE X (X=1):' READ*, BX PRINT*, 'INGRESAR EL NUMBER DE SUBINTERVALOS DE X (N=10):' READ*, NX PRINT*,'INGRESAR EL RANGO INFERIOR DE LA VARIABLE T (T=0):' READ*,AT PRINT*, 'INGRESAR EL RANGO SUPERIOR DE LA VARIABLE T (T=1):' READ*, BT PRINT*, 'INGRESAR EL NUMBER DE SUBINTERVALOS DE T (N= 20):' READ*, NT PRINT*,'' PRINT*,('*',I=1,79) PRINT '(5X,"RESULTADOS COMPUTACIONALES")' PRINT*,('*',I=1,79) PRINT*,'' PI = 4.0*ATAN(1.0) HX=(BX-AX)/NX HT=(BT-AT)/NT DO I=1,NX+1 X(I)=(I-1)*HX ENDDO DO J=1,NT+1 T(J)=(J-1)*HT ENDDO DO I=2,NX X(I)=(I-1)*HX U(I,1)=F(X(I))
  • 3. U(I,2)=U(I,1)+HT*G1(X(I)) ENDDO DO J=1,NT+1 U(1,J)=0 U(NX+1,J)=0 ENDDO A=1 GAM=(A**2)*(HT**2)/(HX**2) WRITE(11,7)AT,(AT+(L1-1)*HT,L1=1,NT+1) !PRINT'(2X,F5.2,21F5.2)',AT,(AT+(L1-1)*HT,L1=1,NT+1) DO J=2,NT DO I=2,NX U(I,J+1)=-U(I,J-1)+GAM*U(I-1,J)+(2-2*GAM)*U(I,J)+GAM*U(I+1,J) ENDDO ENDDO 7 FORMAT (2X,F5.2,21(3X,F5.2)) DO I=1,NX+1 WRITE(11,9)AX,(U(I,J),J=1,NT+1) PRINT '(2X,F5.2,21F8.4)',AX,(U(I,J),J=1,NT+1) AX=AX+HX ENDDO 9 FORMAT(2X,F5.2,21F8.4) PRINT*,'' STOP CONTAINS FUNCTION F(X) REAL X,F F=SIN(PI*X)+0.5*SIN(3*PI*X) RETURN END FUNCTION FUNCTION G1(Y) REAL Y,G1 G1=0+0*Y RETURN END FUNCTION END
  • 4. USANDO SCILAB TENEMOS: function y=fi(x) y=sin(%pi*x)+0.5*sin(3*%pi*x); endfunction function y=psi(x) y=0 endfunction function [u, x, t]=ggg(N, K, L, T, a) h=L/N; delta=T/K;
  • 5. for i=1:N+1 x(i)=(i-1)*h; end for i=2:N x(i)=(i-1)*h; u(i,1)=fi(x(i)); u(i,2)=u(i,1)+delta*psi(x(i)); end for j=1:K+1 t(j)=(j-1)*delta; end for j=1:K+1 u(1,j)=0; u(N+1,j)=0; end gam=a^2*delta^2/h^2; for j=2:K for i=2:N u(i,j+1)=-u(i,j-1)+gam*u(i-1,j)+(2-2*gam)*... u(i,j)+gam*u(i+1,j); end end endfunction a=1; [u,x,t]=ggg(10,20,1,1,a); surf(x,t,u'); xlabel('X','fontsize',4); ylabel('T','fontsize',4); zlabel('U','fontsize',4); title('Solución de una ecuación hiperbólica','fontsize',6);
  • 6. USANDO MATLAB TENEMOS: PP: clear clc fi=@(x)sin(pi*x)+0.5*sin(3*pi*x); psi=@(t)0; a=1; [u,x,t]=ggg(fi,psi,10,20,1,1,a); figure('color',[1,1,1]); surf(x,t,u'); xlabel('X'); ylabel('T'); zlabel('U'); title('Solución de una ecuación hiperbólica'); PS: function [u, x, t]=ggg(fi,psi,N, K, L, T, a) h=L/N; delta=T/K; for i=1:N+1 x(i)=(i-1)*h; end for i=2:N x(i)=(i-1)*h; u(i,1)=fi(x(i)); u(i,2)=u(i,1)+delta*psi(x(i)); end for j=1:K+1 t(j)=(j-1)*delta; end for j=1:K+1 u(1,j)=0; u(N+1,j)=0; end