ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
database_impurity.f90
Go to the documentation of this file.
1 subroutine database_impurity (coreprof_in, coresource_db, coreimpur_db, coresource_new, coreimpur_new)
2 
4  USE deallocate_structures
5 
6  USE itm_constants
7  USE euitm_routines
8  USE euitm_schemas
10  USE copy_structures
11 
12  IMPLICIT NONE
13 
14 
15 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
16 ! +++ CPOs:
17 
18 
19  TYPE (type_coreprof), POINTER :: coreprof_in(:)
20  TYPE (type_coresource), POINTER :: coresource_db(:),coresource_new(:)
21  TYPE (type_coreimpur), POINTER :: coreimpur_db(:), coreimpur_new(:)
22 
23  INTEGER, PARAMETER :: nslice = 1 !number of CPO ocurancies in the work flow
24  INTEGER :: nrho, nrho1
25  INTEGER :: nnucl
26  INTEGER :: nion, iion
27  INTEGER :: nimp
28  INTEGER, ALLOCATABLE :: nzimp(:)
29  INTEGER :: nneut
30  INTEGER, ALLOCATABLE :: ncomp(:)
31  INTEGER, ALLOCATABLE :: ntype(:)
32  REAL(R8),allocatable,dimension(:) :: rho,rho1,fun
33  integer :: nvalues, ivalues,impvalue,iimp
34 
35 !get dimensions, composition from coreprof
36 write(*,*) 'time used',coreprof_in(1)%time
37 nrho = SIZE(coreprof_in(1)%rho_tor, dim=1)
38 write(*,*) 'nrho=', nrho
39  CALL get_comp_dimensions(coreprof_in(1)%COMPOSITIONS, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp)
40 !allocate coreimpur and coresource
41 CALL allocate_coresource_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coresource_new)
42 CALL allocate_coreimpur_cpo(nslice, nrho, nnucl, nion, nimp, nzimp, nneut, ntype, ncomp, coreimpur_new)
43 
44 !allocate temperature as it is not allocated by default
45  do iimp=1,nimp
46  if (.not.associated(coreimpur_new(1)%impurity(iimp)%tz)) &
47  allocate(coreimpur_new(1)%impurity(iimp)%tz(nrho,nzimp(iimp)))
48  enddo
49 
50 
51 !allocate source_id as it is not allocated by default
52 if (.not.associated(coresource_new(1)%VALUES(1)%sourceid%id)) &
53  ALLOCATE (coresource_new(1)%VALUES(1)%sourceid%id(1))
54 if (.not.associated(coresource_new(1)%VALUES(1)%sourceid%description)) &
55  ALLOCATE (coresource_new(1)%VALUES(1)%sourceid%description(1))
56 
57 call copy_cpo(coreprof_in(1)%compositions, coresource_new(1)%compositions)
58 call copy_cpo(coreprof_in(1)%compositions, coreimpur_new(1)%compositions)
59 
60 coreimpur_new(1)%rho_tor=coreprof_in(1)%rho_tor
61 coreimpur_new(1)%rho_tor_norm=coreprof_in(1)%rho_tor_norm
62 coresource_new(1)%values(1)%rho_tor=coreprof_in(1)%rho_tor
63 coresource_new(1)%values(1)%rho_tor_norm=coreprof_in(1)%rho_tor_norm
64 coresource_new(1)%VALUES(1)%sourceid%id = 'impurity'
65 coresource_new(1)%VALUES(1)%sourceid%flag = 29
66 coresource_new(1)%VALUES(1)%sourceid%description = 'Impurity source'
67 
68 allocate (fun(nrho),rho(nrho))
69 rho=coreprof_in(1)%rho_tor
70 
71 !get data from coresource (qe,se)
72 IF(ASSOCIATED(coresource_db)) then
73  nvalues=size(coresource_db(1)%values)
74  !write(*,*) 'nvalues',nvalues
75  write(*,*) 'time from database',coresource_db(1)%time
76  if (nvalues.ge.0) then
77  impvalue=0
78  do ivalues=1,nvalues
79  if (coresource_db(1)%values(ivalues)%sourceid%flag.eq.29) impvalue=ivalues
80  enddo
81  else
82  write(*,*) 'no sources are given on input'
83  end if
84  write(*,*) 'impvalue',impvalue
85  if (associated(coresource_db(1)%values(impvalue)%rho_tor)) then
86  nrho1=size(coresource_db(1)%values(impvalue)%rho_tor)
87  else
88  write(*,*) 'rho_tor from database (coresource) is not found'
89  nrho1=0
90  end if
91  write(*,*) 'nrho1',nrho1
92  allocate(rho1(nrho1))
93  rho1(:)=coresource_db(1)%values(impvalue)%rho_tor(:)
94 !Se
95  if (associated(coresource_db(1)%values(impvalue)%se%exp)) then
96  fun(:) = 0.0_r8
97  IF(ASSOCIATED(coresource_db(1)%VALUES(impvalue)%Se%exp)) THEN
98  !write(*,*) 'se', CORESOURCE_db(1)%VALUES(impvalue)%Se%exp
99  if (all(coresource_db(1)%VALUES(impvalue)%Se%exp==0)) then
100  coresource_new(1)%VALUES(1)%Se%exp(:) = 0.0
101  else
102  CALL l3interp(coresource_db(1)%VALUES(impvalue)%Se%exp, rho1, nrho1, &
103  fun, rho, nrho)
104  coresource_new(1)%VALUES(1)%Se%exp(:) = fun(:)
105  end if
106  END IF
107  end if
108 !Qe
109  if (associated(coresource_db(1)%values(impvalue)%qe%exp)) then
110  fun(:) = 0.0_r8
111  IF(ASSOCIATED(coresource_db(1)%VALUES(impvalue)%qe%exp)) THEN
112  !write(*,*) 'qe',CORESOURCE_db(1)%VALUES(impvalue)%qe%exp
113  CALL l3interp(coresource_db(1)%VALUES(impvalue)%qe%exp, rho1, nrho1, &
114  fun, rho, nrho)
115  coresource_new(1)%VALUES(1)%Qe%exp(:) = fun(:)
116  END IF
117  end if
118 end if
119 write(*,*) 'after coresource'
120 !get data from coreimpur (nz)
121 call interpolate_impur(coreimpur_db(1),coreimpur_new(1))
122 write(*,*) 'after impurity'
123 CALL deallocate_cpo(coresource_db)
124 call deallocate_cpo(coreimpur_db)
125 deallocate(fun,rho,rho1)
126 
127 
128 end subroutine database_impurity
subroutine allocate_coreimpur_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, COREIMPUR)
This routine allocates COREIMPUR CPO.
subroutine fun(X, F)
Definition: Ev2.f:10
subroutine get_comp_dimensions(COMPOSITIONS, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP)
subroutine l3interp(y_in, x_in, nr_in, y_out, x_out, nr_out)
Definition: l3interp.f90:1
subroutine database_impurity(coreprof_in, coresource_db, coreimpur_db, coresource_new, coreimpur_new)
This module contains routines for allocation/deallocation if CPOs used in ETS.
subroutine allocate_coresource_cpo(NSLICE, NRHO, NNUCL, NION, NIMP, NZIMP, NNEUT, NTYPE, NCOMP, CORESOURCE)
This routine allocates CORESOURCE CPO.
subroutine interpolate_impur(COREIMPUR_IN, COREIMPUR_OUT)