Skip to content
Snippets Groups Projects
Commit f34ee449 authored by Antoine Cyril David Hoffmann's avatar Antoine Cyril David Hoffmann :seedling:
Browse files

corrections of small errors detected by the gnu fortran compiler

parent 82e51c51
No related branches found
No related tags found
No related merge requests found
......@@ -79,10 +79,10 @@ CONTAINS
use prec_const
IMPLICIT NONE
CALL find_input_file
NAMELIST /BASIC/ nrun, dt, tmax, maxruntime
CALL find_input_file
READ(lu_in,basic)
!Init cumulative timers
......
......@@ -5,7 +5,6 @@ MODULE coeff
USE PREC_CONST
use BASIC
USE MODEL
USE FMZM
PUBLIC
......
......@@ -525,7 +525,7 @@ CONTAINS
! Ghosts boundaries (depend on the order of z operators)
IF(Nz .EQ. 1) THEN
izgs = izs; izge = ize;
zarray(izs,:) = 0; zarray_full(izs) = 0;
zarray_full(izs) = 0;
ELSEIF(Nz .GE. 4) THEN
izgs = izs - 2; izge = ize + 2;
ELSE
......
......@@ -3,7 +3,7 @@ MODULE numerics
USE prec_const
USE grid
USE utility
USE coeff
implicit none
PUBLIC :: build_dnjs_table, evaluate_kernels, evaluate_EM_op
......@@ -117,7 +117,7 @@ SUBROUTINE evaluate_poisson_op
USE basic
USE array, Only : kernel_e, kernel_i, inv_poisson_op, inv_pol_ion
USE grid
USE model, ONLY : tau_e, tau_i, q_e, q_i, KIN_E
USE model, ONLY : tau_e, tau_i, q_e, q_i, qe2_taue, qi2_taui, KIN_E
IMPLICIT NONE
REAL(dp) :: pol_i, pol_e ! (Z_a^2/tau_a (1-sum_n kernel_na^2))
INTEGER :: ini,ine
......@@ -163,7 +163,7 @@ SUBROUTINE evaluate_ampere_op
USE basic
USE array, Only : kernel_e, kernel_i, inv_ampere_op
USE grid
USE model, ONLY : tau_e, tau_i, q_e, q_i, KIN_E, beta
USE model, ONLY : tau_e, tau_i, q_e, q_i, KIN_E, beta, sigma_e, sigma_i
USE geometry, ONLY : hatB
IMPLICIT NONE
REAL(dp) :: pol_i, pol_e, kperp2 ! (Z_a^2/tau_a (1-sum_n kernel_na^2))
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment