tstExternalMultistep.f90

./Manager/wrap/tests/tstExternalMultistep.f90

2 
5 
6 #include "ScaleSTL/FortranTestMacros.h"
8 
9 use origen_testpaths_m
10 !
11 use nemesis_comm, only: build_types, initialize, finalize, node
12 
13 implicit none
14 
15 type(origen_casewrapper) :: casew1,casew2
16 type(origen_librarywrapper) :: libw
17 
18 integer :: itot,nsteps
19 real(C_DOUBLE), allocatable :: times(:)
20 real(C_DOUBLE),allocatable :: conc_buffer1(:),conc_buffer2(:,:)
21 real(C_DOUBLE), allocatable :: fluxes(:) !will depend on number of steps
22 integer,parameter :: nnucl0=2
23 real(C_DOUBLE) :: conc0(nnucl0)
24 integer :: nucl0(nnucl0), typ0(nnucl0)
25 
26 !important variables
27 integer,allocatable :: all_nucl_in(:), all_typ_in(:)
28 integer,allocatable :: all_nucl_ex(:), all_typ_ex(:)
29 real(C_DOUBLE),allocatable :: conc_in(:,:),conc_ex(:,:)
30 
31 integer :: i,j
32 real(C_DOUBLE) :: dt
33 
34 logical :: file_exists
35 
36 call initialize
37 call build_types
38 if ( node() /=0 ) call finalize
39 
40 inquire(file=ce14_e15_filepath,exist=file_exists)
41 
42 expect_true(file_exists)
43 
44 !! initialize times and fluxes.
45 nsteps=3
46 allocate(times(0:nsteps),fluxes(1:nsteps))
47 dt=100
48 times(0)=0.d0
49 do i=1,nsteps
50  times(i)=times(i-1)+dt
51 end do
52 times=times*86400.d0 !units from days to seconds
53 fluxes=1.e14;
54 
55 !! initialize intial isotopics.
56 nucl0=[922350,922380]
57 conc0=[0.05d0,0.95d0]
58 typ0=[origen_sublib_2ac,origen_sublib_2ac] !Origen_SUBLIB_1LT,Origen_SUBLIB_3FP also available
59 
60 
61 !! Option 1: Let solver make multi-steps.
62 call libw%initialize(ce14_e15_filepath)
63 call libw%set_pos(1)
64 call casew1%initialize(libw)
65 itot = casew1 % total_nuclides()
66 call casew1%set_times(times)
67 call casew1%set_fluxes(fluxes)
68 call casew1%set_initial_concentrations(nnucl0,nucl0,conc0,typ0,origen_concentrationunit_gatoms)
69 call casew1%libw%get_nucl(all_nucl_in)
70 call casew1%libw%get_typ_nuc(all_typ_in)
71 call casew1%run()
72 call casew1%get_concentrations(conc_in)
73 
74 
75 
76 !! Option 2: Make our own external multi-steps.
77 allocate( conc_ex(0:nsteps,1:itot) )
78 allocate(conc_buffer1(itot))
79 call libw%initialize(ce14_e15_filepath) !library must be initialized and loaded OUTSIDE the loop
80 do i=1,nsteps
81  call libw%set_pos(1) !get new cross sections!
82  expect_eq(1,libw%get_pos())
83  call casew2%initialize(libw)
84  itot = casew2 % total_nuclides()
85  call casew2%set_times(times(i-1:i)) !only 1 step
86  call casew2%set_fluxes(fluxes(i:i))
87 
88  !we need a special condition for the first step we will pass in the initial concentrations
89  !which are a much shorter list and we need to get the full nuclide ids and types lists
90  !for future steps
91  if( i==1 )then
92  call casew2%set_initial_concentrations(nnucl0,nucl0,conc0,typ0,origen_concentrationunit_gatoms)
93  call casew2%libw%get_nucl(all_nucl_ex)
94  call casew2%libw%get_typ_nuc(all_typ_ex)
95 
96  !now we are in the general looping regime
97  else
98  conc_buffer1=conc_ex(i-1,1:itot) !pass in beginning of time step concentrations
99  call casew2%set_initial_concentrations_by_vector(conc_buffer1,origen_concentrationunit_gatoms)
100  endif
101 
102  !the big run
103  call casew2%run()
104 
105  !extract beginning and end-of step
106  call casew2%get_concentrations(conc_buffer2)
107  conc_ex(i-1:i,1:itot)=conc_buffer2
108 
109 end do
110 
111 !destroy
112 call casew1%destroy()
113 call casew2%destroy()
114 call libw%destroy()
115 
116 !! Check consistency (but not exact because we change cross sections each time)
117 do j=1,itot
118  expect_eq(all_nucl_in(j), all_nucl_ex(j))
119  expect_eq(all_typ_in(j), all_typ_ex(j))
120  do i = 0, nsteps
121  expect_eq(conc_in(i,j), conc_ex(i,j))
122  end do
123 end do
124 
125 call finalize
126 
127 
128 1001 format('*** Error: nuclide ids do not match for nuclide number j=',i5.5,&
129 'internal (',i7,') vs. external (',i7,')')
130 1002 format('*** Error: nuclide types do not match for nuclide number j=',i5.5,&
131 'internal (',i7,') vs. external (',i7,')')
132 1003 format('*** Error: nuclide concentrations do not match for time step i=',i5.5,' nuclide number j=',i5.5,&
133 'internal (',i7,') vs. external (',i7,')')
134 end program