Skip to content

Commit

Permalink
Uppercase FORTRAN keywords
Browse files Browse the repository at this point in the history
  • Loading branch information
keithbennett committed Jun 26, 2018
1 parent 68a54e3 commit 03058c8
Show file tree
Hide file tree
Showing 9 changed files with 33 additions and 33 deletions.
4 changes: 2 additions & 2 deletions epoch1d/src/physics_packages/collisions.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2189,8 +2189,8 @@ SUBROUTINE test_shuffle
part => partlist%head
DO j = 1, plist_length
histo(j) = histo(j) + part%coll_count
if (minp(j) > part%coll_count) minp(j) = part%coll_count
if (maxp(j) < part%coll_count) maxp(j) = part%coll_count
IF (minp(j) > part%coll_count) minp(j) = part%coll_count
IF (maxp(j) < part%coll_count) maxp(j) = part%coll_count
std_dev(j) = std_dev(j) + part%coll_count**2
part => part%next
END DO
Expand Down
16 changes: 8 additions & 8 deletions epoch1d/src/physics_packages/ionise.F90
Original file line number Diff line number Diff line change
Expand Up @@ -520,7 +520,7 @@ SUBROUTINE multiphoton_tunnelling_bsi
sample = random()
! Calculate probability of ionisation using a cumulative distribution
! function modelling ionisation in a field as an exponential decay
IF (sample < 1.0_num - exp(-1.0_num * rate * time_left)) THEN
IF (sample < 1.0_num - EXP(-1.0_num * rate * time_left)) THEN
IF (species_list(current_state)%release_species > 0) THEN
CALL create_particle(new)
! Create electron for release
Expand Down Expand Up @@ -561,7 +561,7 @@ SUBROUTINE multiphoton_tunnelling_bsi
! Calculates the time of ionisation using inverse sampling, and
! subtracts it from the time step. Ensures diminishing time for
! successive ionisations
time_left = time_left + log(1.0_num - sample) / rate
time_left = time_left + LOG(1.0_num - sample) / rate
! Current correction as proposed from Mulser et al 1998, true from
! ejection energy <e_j> << m_e*c**2, i.e. sub-relativistic ejection
! velocity. This shall be true for all laser gamma factors, as BSI
Expand Down Expand Up @@ -768,7 +768,7 @@ SUBROUTINE multiphoton_tunnelling
sample = random()
! Calculate probability of ionisation using a cumulative distribution
! function modelling ionisation in a field as an exponential decay
IF (sample < 1.0_num - exp(-1.0_num * rate * time_left)) THEN
IF (sample < 1.0_num - EXP(-1.0_num * rate * time_left)) THEN
IF (species_list(current_state)%release_species > 0) THEN
CALL create_particle(new)
! Create electron for release
Expand Down Expand Up @@ -809,7 +809,7 @@ SUBROUTINE multiphoton_tunnelling
! Calculates the time of ionisation using inverse sampling, and
! subtracts it from the time step. Ensures diminishing time for
! successive ionisations
time_left = time_left + log(1.0_num - sample) / rate
time_left = time_left + LOG(1.0_num - sample) / rate
! Current correction as proposed from Mulser et al 1998, true from
! ejection energy <e_j> << m_e*c**2, i.e. sub-relativistic ejection
! velocity. This shall be true for all laser gamma factors, as BSI
Expand Down Expand Up @@ -1019,7 +1019,7 @@ SUBROUTINE tunnelling_bsi
sample = random()
! Calculate probability of ionisation using a cumulative distribution
! function modelling ionisation in a field as an exponential decay
IF (sample < 1.0_num - exp(-1.0_num * rate * time_left)) THEN
IF (sample < 1.0_num - EXP(-1.0_num * rate * time_left)) THEN
IF (species_list(current_state)%release_species > 0) THEN
CALL create_particle(new)
! Create electron for release
Expand Down Expand Up @@ -1051,7 +1051,7 @@ SUBROUTINE tunnelling_bsi
! Calculates the time of ionisation using inverse sampling, and
! subtracts it from the time step. Ensures diminishing time for
! successive ionisations
time_left = time_left + log(1.0_num - sample) / rate
time_left = time_left + LOG(1.0_num - sample) / rate
! Current correction as proposed from Mulser et al 1998, true from
! ejection energy <e_j> << m_e*c**2, i.e. sub-relativistic ejection
! velocity. This shall be true for all laser gamma factors, as BSI
Expand Down Expand Up @@ -1242,7 +1242,7 @@ SUBROUTINE tunnelling
sample = random()
! Calculate probability of ionisation using a cumulative distribution
! function modelling ionisation in a field as an exponential decay
IF (sample < 1.0_num - exp(-1.0_num * rate * time_left)) THEN
IF (sample < 1.0_num - EXP(-1.0_num * rate * time_left)) THEN
IF (species_list(current_state)%release_species > 0) THEN
CALL create_particle(new)
! Create electron for release
Expand Down Expand Up @@ -1274,7 +1274,7 @@ SUBROUTINE tunnelling
! Calculates the time of ionisation using inverse sampling, and
! subtracts it from the time step. Ensures diminishing time for
! successive ionisations
time_left = time_left + log(1.0_num - sample) / rate
time_left = time_left + LOG(1.0_num - sample) / rate
! Current correction as proposed from Mulser et al 1998, true from
! ejection energy <e_j> << m_e*c**2, i.e. sub-relativistic ejection
! velocity. This shall be true for all laser gamma factors, as BSI
Expand Down
2 changes: 1 addition & 1 deletion epoch1d/src/physics_packages/numerics.f90
Original file line number Diff line number Diff line change
Expand Up @@ -687,7 +687,7 @@ REAL(num) FUNCTION rkbesl(x, alpha, nb, ize, ncalc)
d1 = c * d1 + p(i)
t1 = c * t1 + q(i)
END DO
p0 = EXP(c * (a + c * (p(8) - c * d1 / t1) - log(ex))) / ex
p0 = EXP(c * (a + c * (p(8) - c * d1 / t1) - LOG(ex))) / ex
f2 = (c + 0.5_num - ratio) * f1 / ex
bk1 = p0 + (d3 * f0 - f2 + f0 + blpha) / (f2 + f1 + f0) * p0
IF (ize == 1) bk1 = bk1 * EXP(-ex)
Expand Down
4 changes: 2 additions & 2 deletions epoch2d/src/physics_packages/collisions.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2228,8 +2228,8 @@ SUBROUTINE test_shuffle
part => partlist%head
DO j = 1, plist_length
histo(j) = histo(j) + part%coll_count
if (minp(j) > part%coll_count) minp(j) = part%coll_count
if (maxp(j) < part%coll_count) maxp(j) = part%coll_count
IF (minp(j) > part%coll_count) minp(j) = part%coll_count
IF (maxp(j) < part%coll_count) maxp(j) = part%coll_count
std_dev(j) = std_dev(j) + part%coll_count**2
part => part%next
END DO
Expand Down
16 changes: 8 additions & 8 deletions epoch2d/src/physics_packages/ionise.F90
Original file line number Diff line number Diff line change
Expand Up @@ -570,7 +570,7 @@ SUBROUTINE multiphoton_tunnelling_bsi
sample = random()
! Calculate probability of ionisation using a cumulative distribution
! function modelling ionisation in a field as an exponential decay
IF (sample < 1.0_num - exp(-1.0_num * rate * time_left)) THEN
IF (sample < 1.0_num - EXP(-1.0_num * rate * time_left)) THEN
IF (species_list(current_state)%release_species > 0) THEN
CALL create_particle(new)
! Create electron for release
Expand Down Expand Up @@ -611,7 +611,7 @@ SUBROUTINE multiphoton_tunnelling_bsi
! Calculates the time of ionisation using inverse sampling, and
! subtracts it from the time step. Ensures diminishing time for
! successive ionisations
time_left = time_left + log(1.0_num - sample) / rate
time_left = time_left + LOG(1.0_num - sample) / rate
! Current correction as proposed from Mulser et al 1998, true from
! ejection energy <e_j> << m_e*c**2, i.e. sub-relativistic ejection
! velocity. This shall be true for all laser gamma factors, as BSI
Expand Down Expand Up @@ -839,7 +839,7 @@ SUBROUTINE multiphoton_tunnelling
sample = random()
! Calculate probability of ionisation using a cumulative distribution
! function modelling ionisation in a field as an exponential decay
IF (sample < 1.0_num - exp(-1.0_num * rate * time_left)) THEN
IF (sample < 1.0_num - EXP(-1.0_num * rate * time_left)) THEN
IF (species_list(current_state)%release_species > 0) THEN
CALL create_particle(new)
! Create electron for release
Expand Down Expand Up @@ -880,7 +880,7 @@ SUBROUTINE multiphoton_tunnelling
! Calculates the time of ionisation using inverse sampling, and
! subtracts it from the time step. Ensures diminishing time for
! successive ionisations
time_left = time_left + log(1.0_num - sample) / rate
time_left = time_left + LOG(1.0_num - sample) / rate
! Current correction as proposed from Mulser et al 1998, true from
! ejection energy <e_j> << m_e*c**2, i.e. sub-relativistic ejection
! velocity. This shall be true for all laser gamma factors, as BSI
Expand Down Expand Up @@ -1111,7 +1111,7 @@ SUBROUTINE tunnelling_bsi
sample = random()
! Calculate probability of ionisation using a cumulative distribution
! function modelling ionisation in a field as an exponential decay
IF (sample < 1.0_num - exp(-1.0_num * rate * time_left)) THEN
IF (sample < 1.0_num - EXP(-1.0_num * rate * time_left)) THEN
IF (species_list(current_state)%release_species > 0) THEN
CALL create_particle(new)
! Create electron for release
Expand Down Expand Up @@ -1143,7 +1143,7 @@ SUBROUTINE tunnelling_bsi
! Calculates the time of ionisation using inverse sampling, and
! subtracts it from the time step. Ensures diminishing time for
! successive ionisations
time_left = time_left + log(1.0_num - sample) / rate
time_left = time_left + LOG(1.0_num - sample) / rate
! Current correction as proposed from Mulser et al 1998, true from
! ejection energy <e_j> << m_e*c**2, i.e. sub-relativistic ejection
! velocity. This shall be true for all laser gamma factors, as BSI
Expand Down Expand Up @@ -1355,7 +1355,7 @@ SUBROUTINE tunnelling
sample = random()
! Calculate probability of ionisation using a cumulative distribution
! function modelling ionisation in a field as an exponential decay
IF (sample < 1.0_num - exp(-1.0_num * rate * time_left)) THEN
IF (sample < 1.0_num - EXP(-1.0_num * rate * time_left)) THEN
IF (species_list(current_state)%release_species > 0) THEN
CALL create_particle(new)
! Create electron for release
Expand Down Expand Up @@ -1387,7 +1387,7 @@ SUBROUTINE tunnelling
! Calculates the time of ionisation using inverse sampling, and
! subtracts it from the time step. Ensures diminishing time for
! successive ionisations
time_left = time_left + log(1.0_num - sample) / rate
time_left = time_left + LOG(1.0_num - sample) / rate
! Current correction as proposed from Mulser et al 1998, true from
! ejection energy <e_j> << m_e*c**2, i.e. sub-relativistic ejection
! velocity. This shall be true for all laser gamma factors, as BSI
Expand Down
2 changes: 1 addition & 1 deletion epoch2d/src/physics_packages/numerics.f90
Original file line number Diff line number Diff line change
Expand Up @@ -687,7 +687,7 @@ REAL(num) FUNCTION rkbesl(x, alpha, nb, ize, ncalc)
d1 = c * d1 + p(i)
t1 = c * t1 + q(i)
END DO
p0 = EXP(c * (a + c * (p(8) - c * d1 / t1) - log(ex))) / ex
p0 = EXP(c * (a + c * (p(8) - c * d1 / t1) - LOG(ex))) / ex
f2 = (c + 0.5_num - ratio) * f1 / ex
bk1 = p0 + (d3 * f0 - f2 + f0 + blpha) / (f2 + f1 + f0) * p0
IF (ize == 1) bk1 = bk1 * EXP(-ex)
Expand Down
4 changes: 2 additions & 2 deletions epoch3d/src/physics_packages/collisions.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2264,8 +2264,8 @@ SUBROUTINE test_shuffle
part => partlist%head
DO j = 1, plist_length
histo(j) = histo(j) + part%coll_count
if (minp(j) > part%coll_count) minp(j) = part%coll_count
if (maxp(j) < part%coll_count) maxp(j) = part%coll_count
IF (minp(j) > part%coll_count) minp(j) = part%coll_count
IF (maxp(j) < part%coll_count) maxp(j) = part%coll_count
std_dev(j) = std_dev(j) + part%coll_count**2
part => part%next
END DO
Expand Down
16 changes: 8 additions & 8 deletions epoch3d/src/physics_packages/ionise.F90
Original file line number Diff line number Diff line change
Expand Up @@ -620,7 +620,7 @@ SUBROUTINE multiphoton_tunnelling_bsi
sample = random()
! Calculate probability of ionisation using a cumulative distribution
! function modelling ionisation in a field as an exponential decay
IF (sample < 1.0_num - exp(-1.0_num * rate * time_left)) THEN
IF (sample < 1.0_num - EXP(-1.0_num * rate * time_left)) THEN
IF (species_list(current_state)%release_species > 0) THEN
CALL create_particle(new)
! Create electron for release
Expand Down Expand Up @@ -661,7 +661,7 @@ SUBROUTINE multiphoton_tunnelling_bsi
! Calculates the time of ionisation using inverse sampling, and
! subtracts it from the time step. Ensures diminishing time for
! successive ionisations
time_left = time_left + log(1.0_num - sample) / rate
time_left = time_left + LOG(1.0_num - sample) / rate
! Current correction as proposed from Mulser et al 1998, true from
! ejection energy <e_j> << m_e*c**2, i.e. sub-relativistic ejection
! velocity. This shall be true for all laser gamma factors, as BSI
Expand Down Expand Up @@ -910,7 +910,7 @@ SUBROUTINE multiphoton_tunnelling
sample = random()
! Calculate probability of ionisation using a cumulative distribution
! function modelling ionisation in a field as an exponential decay
IF (sample < 1.0_num - exp(-1.0_num * rate * time_left)) THEN
IF (sample < 1.0_num - EXP(-1.0_num * rate * time_left)) THEN
IF (species_list(current_state)%release_species > 0) THEN
CALL create_particle(new)
! Create electron for release
Expand Down Expand Up @@ -951,7 +951,7 @@ SUBROUTINE multiphoton_tunnelling
! Calculates the time of ionisation using inverse sampling, and
! subtracts it from the time step. Ensures diminishing time for
! successive ionisations
time_left = time_left + log(1.0_num - sample) / rate
time_left = time_left + LOG(1.0_num - sample) / rate
! Current correction as proposed from Mulser et al 1998, true from
! ejection energy <e_j> << m_e*c**2, i.e. sub-relativistic ejection
! velocity. This shall be true for all laser gamma factors, as BSI
Expand Down Expand Up @@ -1203,7 +1203,7 @@ SUBROUTINE tunnelling_bsi
sample = random()
! Calculate probability of ionisation using a cumulative distribution
! function modelling ionisation in a field as an exponential decay
IF (sample < 1.0_num - exp(-1.0_num * rate * time_left)) THEN
IF (sample < 1.0_num - EXP(-1.0_num * rate * time_left)) THEN
IF (species_list(current_state)%release_species > 0) THEN
CALL create_particle(new)
! Create electron for release
Expand Down Expand Up @@ -1235,7 +1235,7 @@ SUBROUTINE tunnelling_bsi
! Calculates the time of ionisation using inverse sampling, and
! subtracts it from the time step. Ensures diminishing time for
! successive ionisations
time_left = time_left + log(1.0_num - sample) / rate
time_left = time_left + LOG(1.0_num - sample) / rate
! Current correction as proposed from Mulser et al 1998, true from
! ejection energy <e_j> << m_e*c**2, i.e. sub-relativistic ejection
! velocity. This shall be true for all laser gamma factors, as BSI
Expand Down Expand Up @@ -1468,7 +1468,7 @@ SUBROUTINE tunnelling
sample = random()
! Calculate probability of ionisation using a cumulative distribution
! function modelling ionisation in a field as an exponential decay
IF (sample < 1.0_num - exp(-1.0_num * rate * time_left)) THEN
IF (sample < 1.0_num - EXP(-1.0_num * rate * time_left)) THEN
IF (species_list(current_state)%release_species > 0) THEN
CALL create_particle(new)
! Create electron for release
Expand Down Expand Up @@ -1500,7 +1500,7 @@ SUBROUTINE tunnelling
! Calculates the time of ionisation using inverse sampling, and
! subtracts it from the time step. Ensures diminishing time for
! successive ionisations
time_left = time_left + log(1.0_num - sample) / rate
time_left = time_left + LOG(1.0_num - sample) / rate
! Current correction as proposed from Mulser et al 1998, true from
! ejection energy <e_j> << m_e*c**2, i.e. sub-relativistic ejection
! velocity. This shall be true for all laser gamma factors, as BSI
Expand Down
2 changes: 1 addition & 1 deletion epoch3d/src/physics_packages/numerics.f90
Original file line number Diff line number Diff line change
Expand Up @@ -687,7 +687,7 @@ REAL(num) FUNCTION rkbesl(x, alpha, nb, ize, ncalc)
d1 = c * d1 + p(i)
t1 = c * t1 + q(i)
END DO
p0 = EXP(c * (a + c * (p(8) - c * d1 / t1) - log(ex))) / ex
p0 = EXP(c * (a + c * (p(8) - c * d1 / t1) - LOG(ex))) / ex
f2 = (c + 0.5_num - ratio) * f1 / ex
bk1 = p0 + (d3 * f0 - f2 + f0 + blpha) / (f2 + f1 + f0) * p0
IF (ize == 1) bk1 = bk1 * EXP(-ex)
Expand Down

0 comments on commit 03058c8

Please sign in to comment.