Skip to content
Snippets Groups Projects
Commit e53c6d14 authored by Wiarda, Dorothea's avatar Wiarda, Dorothea
Browse files

Remove the Ener0 energy grid.

parent 32744947
No related branches found
No related tags found
No related merge requests found
......@@ -116,8 +116,6 @@ module exploc_common_m
real(kind=8),allocatable,dimension(:)::A_Iddcov
integer, pointer :: Iu => Loc(120)
integer, pointer :: Ienerg => Loc(121)
real(kind=8),allocatable,target,dimension(:)::A_Iener0_r
real(kind=8),pointer,dimension(:)::A_Iener0
integer, pointer :: Ienerb => Loc(124)
integer, pointer :: Ith => Loc(125)
......@@ -590,12 +588,6 @@ module exploc_common_m
!!$ integer, pointer :: Iu => Loc(120)
!!$ integer, pointer :: Ienerg => Loc(121)
subroutine make_A_Iener0(want)
integer::want
nullify(A_Iener0)
call allocate_real_data(A_Iener0_r,want)
A_Iener0 => A_Iener0_r
end subroutine make_A_Iener0
!!$ integer, pointer :: Ienerb => Loc(124)
......
......@@ -89,10 +89,6 @@ module Samdat_0_M
!
! ### one ###
Ienerg = Idimen (Ndat, 1, 'Ndat, 1')
A_Iener0 => A(Ienerg:Ienerg+Ndat+1)
IF (Ktzero.NE.0) then
call make_A_Iener0(Ndat)
end if
!
! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - <
! ### one.one ###
......@@ -176,8 +172,8 @@ module Samdat_0_M
! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - >
!
! *** modify energies via Tzero, Elzero
IF (Ktzero.NE.0) CALL Mtzero (A(Ienerg), A_Iener0, Ndat)
IF (Ktzero.NE.0) CALL Mtzero (A(Ie), A(Ie), Ndatb)
IF (Ktzero.NE.0) CALL Mtzero (A(Ienerg), Ndat)
IF (Ktzero.NE.0) CALL Mtzero (A(Ie), Ndatb)
!
IF (Kphase.NE.0) THEN
! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - <
......@@ -292,7 +288,6 @@ module Samdat_0_M
CALL Artificial_Energy (A(Ienerg), Ndat, Keveng)
I = Idimen (Ienerg, -1, 'Ienerg, -1')
Ienerg = Idimen (Ndat, 1, 'Ndat, 1')
A_Iener0 => A(Ienerg:Ienerg+Ndat+1)
IF (Emin.NE.Emind .OR. Emax.NE.Emaxd) THEN
Ienerb = Idimen (Ndatb, 1, 'Ndatb, 1')
ELSE
......@@ -431,13 +426,12 @@ module Samdat_0_M
!
! ______________________________________________________________
!
SUBROUTINE Mtzero (Energy, Energ0, Nnnnnn)
SUBROUTINE Mtzero (Energy, Nnnnnn)
!
use fixedr_m
IMPLICIT DOUBLE PRECISION (a-h,o-z)
DIMENSION Energy(*), Energ0(*)
DIMENSION Energy(*)
DO I=1,Nnnnnn
Energ0(I) = Energy(I)
Energy(I) = Energy(I)* &
( Elzero/(1.0d0-Tzero*dsqrt(Energy(I))/Tttzzz) )**2
END DO
......
......@@ -300,7 +300,7 @@ C - - - - - - - - - - - - - - - - - - - - - - - - - <
Idum = Idimen (N, 1, 'N, 1')
N = (Nblmax+1)
Iblock = Idimen (n, 1, 'n, 1')
CALL Thodf (A_Iener0, A(Ie), A(Id), A(Idum),
CALL Thodf (A(Ie), A(Id), A(Idum),
* A(Iblock), Nblmax)
C *** Routine Thodf writes the ORELA-Data-Formt file to be
C *** used for plotting
......
......@@ -2,7 +2,7 @@ C
C
C _________________________________________________________________
C
SUBROUTINE Thodf (Energ0, Energy, Data, Dum, Block, Nblock)
SUBROUTINE Thodf (Energy, Data, Dum, Block, Nblock)
C
C *** Purpose -- Fill section 4 or 5 (and maybe 8 or 9) of "regular" odf
C *** file (the one that has data in section 2 and maybe 6)
......@@ -15,9 +15,12 @@ C
use abro_common_m
use cbro_common_m
use lbro_common_m
use EndfData_common_m
use GridData_M
IMPLICIT DOUBLE PRECISION (a-h,o-z)
C
DIMENSION Energ0(*), Energy(*), Data(*), Dum(*), Block(*)
type(GridData)::grid
DIMENSION Energy(*), Data(*), Dum(*), Block(*)
C DIMENSION Energy(Ndat), Data(Ndat*Numcro)
Data Zero /0.0d0/, One /1.0d0/
C
......@@ -33,7 +36,8 @@ C *** Open the ODF file and find the starting Energy
Nzero = 0
CALL Pltio (Numodf, 'SAMMY.ODF ', Nzero, Nsect, Nch, Kkk)
C
Eee = Energ0(Nnn)*Odffff
call expData%getGrid(grid, 1) ! original user supplied energy grid
Eee = grid%getData(1, 1)*Odffff
K = MIN0 (Nblock, Nch)
Isc = 1
C K=NUMBER OF CHANNELS TO READ THIS TIME (Max=Nblock)
......
......@@ -118,7 +118,7 @@ C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - <
Idum = Idimen (N, 1, 'N, 1')
N = (Nblmax+1)
Iblock = Idimen (N, 1, 'N, 1')
CALL Thodf (A_Iener0, A(Ie), A(Iwsigx), A(Idum),
CALL Thodf (A(Ie), A(Iwsigx), A(Idum),
* A(Iblock), Nblmax)
C *** Routine Thodf writes the ORELA-Data-Formt file to be
C *** used for plotting
......
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