Hi everyone,
I’m encountering a segmentation fault in my Fortran program related to dynamic arrays and file reading. My code reads data from two input files, allocates arrays dynamically (e.g., A
, K
, res
), and passes them to a subroutine (calcul_residus
). Despite initializing and checking array sizes, I still get “Program received signal SIGSEGV: Segmentation fault - invalid memory reference.”
Here’s a brief outline:
- Allocate arrays based on user input (e.g.,
allocate(A(...), K(...), res(...))
). - Read file data for variables like
F%z
, and process them in a subroutine. - Crash occurs when calling
calcul_residus
or accessing array elements.
I’m a beginner in Fortran, so I apologize if my code is rudimentary or too long. I’ve included my code below for context—sorry if parts are in French (I’m a French speaker), but it shouldn’t stop you from understanding it. Thanks in advance for your help!
program LectureDesDonnees
use types_module
implicit none
doubleprecision, external :: calculer_Ki
!! Interface explicite pour calcul_residus !!
interface
subroutine calcul_residus(A, nombre_constituants, F_flash, F, K, res)
use types_module
implicit none
doubleprecision, intent(in) :: A(:), K(:)
doubleprecision, intent(out) :: res(:)
integer, intent(in) :: nombre_constituants
type(flash), intent(in) :: F_flash
type(alimentation), intent(in) :: F
end subroutine calcul_residus
end interface
!! Déclarations des variables globales !!
type(alimentation) :: F
type(flash) :: F_flash
character(len=100) :: ligne, nom, compose_selectionne
integer :: controle_ouverture, controle_lecture, nombre_constituants
integer :: i, j, err
logical :: compose_trouve, nom_valide
character(len=1) :: premiere_lettre
doubleprecision, allocatable :: A(:)
doubleprecision :: w, T, Hv, hl, HF
doubleprecision,allocatable :: x(:), y(:)
doubleprecision, allocatable :: K(:)
doubleprecision, allocatable :: z(:)
doubleprecision, allocatable :: res(:)
!! Lecture des paramètres du séparateur flash !!
open(20, file="parametres_flash.txt", status='old', action='read', &
iostat=controle_ouverture)
if (controle_ouverture /= 0) then
print *, "Erreur : Impossible d'ouvrir parametres_flash.txt"
stop
end if
read(20, *, iostat=controle_lecture) F_flash%P_flash
if (controle_lecture /= 0) then
print *, "Erreur : Lecture pression flash échouée."
stop
end if
read(20, *, iostat=controle_lecture) F_flash%Q_flash
if (controle_lecture /= 0) then
print *, "Erreur : Lecture puissance flash échouée."
stop
end if
read(20, *, iostat=controle_lecture) F_flash%T_ref
if (controle_lecture /= 0) then
print *, "Erreur : Lecture T_ref flash échouée."
stop
end if
print *, "Parametres du separateur flash :"
print *, "Pression du flash : ", F_flash%P_flash, " atm"
print *, "Puissance echangee du flash :", F_flash%Q_flash, " W"
print *, "Temperature de reference : ", F_flash%T_ref, " K"
close(20)
!! Ouverture du fichier donnees_constituants.txt !!
open(10, file="donnees_constituants.txt", status='old', action='read', &
iostat=controle_ouverture)
if (controle_ouverture /= 0) then
print *, "Erreur : Impossible d'ouvrir donnees_constituants.txt"
stop
end if
!! Lecture paramètres alimentation !!
do
print *, "Entrez le debit massique de l'alimentation (en kg/h) :"
read (*, *, iostat=controle_lecture) F%M
if (controle_lecture /= 0 .or. F%M <= 0.0) then
print *, "Erreur : Vous devez entrer un débit massique valide. Veuillez reessayer."
else
exit
end if
end do
do
print *, "Entrez la temperature de l'alimentation (en K) :"
read (*, *, iostat=controle_lecture) F%T
if (controle_lecture /= 0) then
print *, "Erreur : Vous devez entrer une temperature valide."
else
exit
end if
end do
do
print *, "Entrez la pression de l'alimentation (en atm) :"
read (*, *, iostat=controle_lecture) F%P
if (controle_lecture /= 0 .or. F%P <= 0.0) then
print *, "Erreur : Vous devez entrer une pression valide."
else
exit
end if
end do
do
print *, "Entrez le nombre de constituants de l'alimentation (en chiffre) :"
read(*, *, iostat=controle_lecture) nombre_constituants
if (controle_lecture /= 0) then
print *, "Erreur : Vous devez entrer un nombre valide. Veuillez reessayer."
else if (nombre_constituants <= 0) then
print *, "Erreur : Le nombre doit etre superieur a 0. Veuillez reessayer."
else
exit
end if
end do
!! Allocation !!
allocate(y(nombre_constituants), stat=err)
allocate(x(nombre_constituants), stat=err)
allocate(F%constituants(nombre_constituants), stat=err)
allocate(F%z(nombre_constituants), stat=err)
if (err /= 0) then
print *, "Erreur lors de l'allocation de memoire"
stop
end if
!! Lecture constituants !!
F%somme_z = 0.0
do i = 1, nombre_constituants
nom_valide = .false.
do while (.not. nom_valide)
print *, "Entrez le nom du constituant : ", i, "/", nombre_constituants, ":"
read(*,'(A)') compose_selectionne
premiere_lettre = compose_selectionne(1:1)
if (iachar(premiere_lettre)<iachar('A') .or. &
iachar(premiere_lettre)>iachar('Z')) then
print *, "Erreur : La première lettre doit etre en majuscule. Veuillez réessayer"
else
nom_valide = .true.
F%constituants(i)%nom = trim(adjustl(compose_selectionne))
end if
end do
do
print *, "Entrez la fraction massique du constituant", &
trim(adjustl(compose_selectionne)), &
" (entre 0 et 1, ex: 0.2) : "
read(*,*, iostat=controle_lecture) F%z(i)
if (controle_lecture /= 0 .or. F%z(i)<0.0 .or. F%z(i)>1.0) then
print *, "Erreur : La fraction massique doit être un nombre entre 0 et 1. Veuillez réessayer."
else
F%somme_z = F%somme_z + F%z(i)
exit
end if
end do
compose_trouve=.false.
rewind(10)
do
read(10,'(A)', iostat=controle_lecture) nom
if (controle_lecture/=0) exit
if (trim(adjustl(nom))=="") cycle
if (trim(adjustl(nom))==trim(adjustl(compose_selectionne))) then
compose_trouve=.true.
read(10,*, iostat=controle_lecture) F%constituants(i)%Cpliq
read(10,*, iostat=controle_lecture) F%constituants(i)%Cpvap
read(10,*, iostat=controle_lecture) F%constituants(i)%Teb
read(10,*, iostat=controle_lecture) F%constituants(i)%Hvap
read(10,*, iostat=controle_lecture) F%constituants(i)%Ai
read(10,*, iostat=controle_lecture) F%constituants(i)%Bi
read(10,*, iostat=controle_lecture) F%constituants(i)%Ci
exit
else
do j=1,7
read(10,*, iostat=controle_lecture)
if (controle_lecture/=0) exit
end do
end if
end do
if (.not. compose_trouve) then
print *, "Erreur : Constituant non trouvé dans le fichier."
end if
end do
close(10)
if (abs(F%somme_z - 1.0)>1e-6) then
print *, "Erreur : Somme des fractions massiques !=1 : ", F%somme_z
stop
end if
!! Calcul K !!
do i=1,nombre_constituants
K(i) = calculer_Ki(F%constituants(i)%Ai, F%constituants(i)%Bi, &
F%constituants(i)%Ci, T, F_flash%P_flash)
end do
!! Allocation des tableaux
allocate(A(2 * nombre_constituants + 2), stat=err)
if (err /= 0) then
print *, "Erreur lors de l'allocation de A"
stop
end if
A = 0.0
allocate(K(nombre_constituants), stat=err)
if (err /= 0) then
print *, "Erreur lors de l'allocation de K"
stop
end if
K = 0.0
allocate(res(2 + 2 * nombre_constituants), stat=err)
if (err /= 0) then
print *, "Erreur lors de l'allocation de res"
stop
end if
res = 0.0
!! Initialisation w, x, y, T !!
w = 0.5
do i=1,nombre_constituants
y(i) = 0.1
x(i) = 0.2
end do
T=0.0
do i=1,nombre_constituants
T = T + F%constituants(i)%Teb * F%z(i)
end do
do i = 1, nombre_constituants
A(i) = 0.2 ! Fraction liquide initiale
A(nombre_constituants + i) = 0.8 ! Fraction vapeur initiale
end do
A(2 * nombre_constituants + 1) = w
A(2 * nombre_constituants + 2) = T
if (size(A) /= 2 * nombre_constituants + 2) then
print *, "Erreur : Dimension incorrecte de A dans calcul_residus."
stop
end if
if (size(res) /= 2 + 2 * nombre_constituants) then
print *, “Erreur : Dimension incorrecte de res dans calcul_residus.”
stop
end if
print *, “Avant calcul_residus :”
print *, “Taille de A :”, size(A), “Valeurs :”, A
print *, “Taille de K :”, size(K), “Valeurs :”, K
!! Appel de la sous-routine calcul_residus !!
call calcul_residus(A, nombre_constituants, F_flash, F, K, res)
!! Affichage des résidus !!
print *, "Résidus calculés :"
do i = 1, size(res)
print *, "R(", i, ") = ", res(i)
end do
!! Libération de la mémoire !!
deallocate(A, res, K)
end program LectureDesDonnees
!===========================================
! Fonction calculer_Ki
!===========================================
function calculer_Ki(Ai, Bi, Ci, T, P_flash)
implicit none
doubleprecision, intent(in) :: Ai, Bi, Ci, T, P_flash
doubleprecision :: calculer_Ki, Psat
!! Calcul de Psat avec la loi d'Antoine !!
Psat = exp(Ai - Bi / (T + Ci))
calculer_Ki = Psat / P_flash
end function calculer_Ki
!===========================================
! Subroutine calcul_residus
!===========================================
subroutine calcul_residus(A, nombre_constituants, F_flash, F, K, res)
use types_module
implicit none
doubleprecision, intent(in) :: A(:), K(
doubleprecision, intent(out) :: res(
integer, intent(in) :: nombre_constituants
type(flash), intent(in) :: F_flash
type(alimentation), intent(in) :: F
integer :: i
doubleprecision :: w, T, Hv, hl, HF
if (size(A) /= 2 * nombre_constituants + 2) then
print *, "Erreur : Dimension incorrecte de A dans calcul_residus."
stop
end if
if (size(res) /= 2 + 2 * nombre_constituants) then
print *, “Erreur : Dimension incorrecte de res dans calcul_residus.”
stop
end if
!! Initialisation des inconnues !!
w = A(2 * nombre_constituants + 1)
T = A(2 * nombre_constituants + 2)
print *, “Taille de A :”, size(A)
print *, “Taille de res :”, size(res)
print *, “Fraction vapeur w :”, w
print *, “Température T :”, T
!! Calcul des résidus !!
res(1) = 0.0 ! Résidu énergétique
res(2) = 0.0 ! Résidu différentiel
do i = 1, nombre_constituants
res(2 + i) = w * A(nombre_constituants + i) + (1.0 - w) * A(i) - F%z(i)
res(2 + nombre_constituants + i) = A(nombre_constituants + i) - K(i) * A(i)
end do
end subroutine calcul_residus