ETS  \$Id: Doxyfile 2162 2020-02-26 14:16:09Z g2dpc $
 All Classes Files Functions Variables Pages
copy_cpo_ets.f90
Go to the documentation of this file.
1 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
7 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
9 
10 CONTAINS
11 
12 
13 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
19 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
20  SUBROUTINE copy_boundary_cond (COREPROF_IN, COREPROF_OUT)
21 
22  USE euitm_schemas
23 
24  IMPLICIT NONE
25 
26 
27  TYPE (type_coreprof), POINTER :: coreprof_in(:)
28  TYPE (type_coreprof), POINTER :: coreprof_out(:)
29 
30 
31  coreprof_out(1)%psi%boundary%value = coreprof_in(1)%psi%boundary%value
32  coreprof_out(1)%psi%boundary%type = coreprof_in(1)%psi%boundary%type
33 
34  coreprof_out(1)%ni%boundary%value = coreprof_in(1)%ni%boundary%value
35  coreprof_out(1)%ni%boundary%type = coreprof_in(1)%ni%boundary%type
36 
37  coreprof_out(1)%ti%boundary%value = coreprof_in(1)%ti%boundary%value
38  coreprof_out(1)%ti%boundary%type = coreprof_in(1)%ti%boundary%type
39 
40  coreprof_out(1)%te%boundary%value = coreprof_in(1)%te%boundary%value
41  coreprof_out(1)%te%boundary%type = coreprof_in(1)%te%boundary%type
42 
43  coreprof_out(1)%vtor%boundary%value = coreprof_in(1)%vtor%boundary%value
44  coreprof_out(1)%vtor%boundary%type = coreprof_in(1)%vtor%boundary%type
45 
46 
47  RETURN
48 
49  END SUBROUTINE copy_boundary_cond
50 
51 
52 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
53 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
54 
55 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
61 ! + + + + + + + + + + + + + + + + + + + + + + + + + + + +
62  SUBROUTINE copy_codeparam (CODEPARAM_IN, CODEPARAM_OUT)
63 
64  USE euitm_schemas
65 
66  IMPLICIT NONE
67 
68 
69  TYPE (type_codeparam) :: codeparam_in
70  TYPE (type_codeparam) :: codeparam_out
71 
72  if(associated(codeparam_out%codename)) then
73 ! write(*,*) 'copy_codeparam dealloc codename'
74  deallocate(codeparam_out%codename)
75  endif
76  allocate(codeparam_out%codename(size(codeparam_in%codename)))
77  codeparam_out%codename = codeparam_in%codename
78 
79  if(associated(codeparam_out%codeversion)) then
80 ! write(*,*) 'copy_codeparam dealloc codeversion'
81  deallocate(codeparam_out%codeversion)
82  endif
83  allocate(codeparam_out%codeversion(size(codeparam_in%codeversion)))
84  codeparam_out%codeversion = codeparam_in%codeversion
85 
86  if(associated(codeparam_out%parameters)) then
87 ! write(*,*) 'copy_codeparam dealloc parameters'
88  deallocate(codeparam_out%parameters)
89  endif
90  allocate(codeparam_out%parameters(size(codeparam_in%parameters)))
91  codeparam_out%parameters = codeparam_in%parameters
92 !!! codeparam_out%output_diag = codeparam_in%output_diag
93  codeparam_out%output_flag = codeparam_in%output_flag
94 
95  RETURN
96 
97  END SUBROUTINE copy_codeparam
98 
99 END MODULE copy_cpo_ets
subroutine copy_codeparam(CODEPARAM_IN, CODEPARAM_OUT)
COPY CODEPARAM.
Module provides routines for copying parts of CPOs (COREPROF and EQUILIBRIUM)
Definition: copy_cpo_ets.f90:8
subroutine copy_boundary_cond(COREPROF_IN, COREPROF_OUT)