3 ! Check error of pr65894 are fixed.
4 ! Contributed by Juergen Reuter <juergen.reuter@desy.de>
5 ! Andre Vehreschild <vehre@gcc.gnu.org>
8 ! Minimal iso_varying_string implementation needed.
13 character(len
=1), dimension(:), allocatable
:: cs
17 elemental
function var_str(c
) result (s
)
18 character(*), intent(in
) :: c
29 end module simple_string
36 public
:: field_data_t
37 public
:: model_data_t
42 type(string_t
), dimension(:), allocatable
:: name
44 procedure
:: init
=> field_data_init
45 procedure
:: get_pdg
=> field_data_get_pdg
50 type(string_t
) :: name
51 type(field_data_t
), dimension(:), allocatable
:: field
53 generic
:: init
=> model_data_init
54 procedure
, private
:: model_data_init
55 generic
:: get_pdg
=> &
56 model_data_get_field_pdg_index
57 procedure
, private
:: model_data_get_field_pdg_index
58 generic
:: get_field_ptr
=> &
59 model_data_get_field_ptr_pdg
60 procedure
, private
:: model_data_get_field_ptr_pdg
61 procedure
:: get_field_ptr_by_index
=> model_data_get_field_ptr_index
62 procedure
:: init_sm_test
=> model_data_init_sm_test
67 subroutine field_data_init (prt
, pdg
)
68 class(field_data_t
), intent(out
) :: prt
69 integer, intent(in
) :: pdg
71 end subroutine field_data_init
73 elemental
function field_data_get_pdg (prt
) result (pdg
)
75 class(field_data_t
), intent(in
) :: prt
77 end function field_data_get_pdg
79 subroutine model_data_init (model
, name
, &
81 class(model_data_t
), intent(out
) :: model
82 type(string_t
), intent(in
) :: name
83 integer, intent(in
) :: n_field
85 allocate (model
%field (n_field
))
86 end subroutine model_data_init
88 function model_data_get_field_pdg_index (model
, i
) result (pdg
)
89 class(model_data_t
), intent(in
) :: model
90 integer, intent(in
) :: i
92 pdg
= model
%field(i
)%get_pdg ()
93 end function model_data_get_field_pdg_index
95 function model_data_get_field_ptr_pdg (model
, pdg
, check
) result (ptr
)
96 class(model_data_t
), intent(in
), target
:: model
97 integer, intent(in
) :: pdg
98 logical, intent(in
), optional
:: check
99 type(field_data_t
), pointer :: ptr
100 integer :: i
, pdg_abs
106 if (lbound(model
%field
, 1) /= 1) call abort()
107 if (ubound(model
%field
, 1) /= 19) call abort()
108 do i
= 1, size (model
%field
)
109 if (model
%field(i
)%get_pdg () == pdg_abs
) then
110 ptr
=> model
%field(i
)
115 end function model_data_get_field_ptr_pdg
117 function model_data_get_field_ptr_index (model
, i
) result (ptr
)
118 class(model_data_t
), intent(in
), target
:: model
119 integer, intent(in
) :: i
120 type(field_data_t
), pointer :: ptr
121 if (lbound(model
%field
, 1) /= 1) call abort()
122 if (ubound(model
%field
, 1) /= 19) call abort()
123 ptr
=> model
%field(i
)
124 end function model_data_get_field_ptr_index
126 subroutine model_data_init_sm_test (model
)
127 class(model_data_t
), intent(out
) :: model
128 type(field_data_t
), pointer :: field
129 integer, parameter :: n_field
= 19
130 call model
%init (var_str ("SM_test"), &
132 field
=> model
%get_field_ptr_by_index (1)
134 end subroutine model_data_init_sm_test
136 end module model_data
149 type(field_data_t
), pointer :: field_data
=> null ()
153 procedure
, private
:: flavor_init0_model
158 impure elemental
subroutine flavor_init0_model (flv
, f
, model
)
159 class(flavor_t
), intent(inout
) :: flv
160 integer, intent(in
) :: f
161 class(model_data_t
), intent(in
), target
:: model
162 ! Check the field l/ubound at various stages, because w/o the patch
163 ! the bounds get mixed up.
164 if (lbound(model
%field
, 1) /= 1) call abort()
165 if (ubound(model
%field
, 1) /= 19) call abort()
167 flv
%field_data
=> model
%get_field_ptr (f
, check
=.true
.)
168 end subroutine flavor_init0_model
179 subroutine beam_1 (u
)
180 integer, intent(in
) :: u
181 type(flavor_t
), dimension(2) :: flv
182 real, dimension(2) :: pol_f
183 type(model_data_t
), target
:: model
184 call model
%init_sm_test ()
185 call flv
%init ([1,-1], model
)
187 end subroutine beam_1
188 subroutine beam_2 (u
, model
)
189 integer, intent(in
) :: u
190 type(flavor_t
), dimension(2) :: flv
191 real, dimension(2) :: pol_f
192 class(model_data_t
), intent(in
), target
:: model
193 call flv
%init ([1,-1], model
)
195 end subroutine beam_2
199 ! This module is just here for a compile check.
202 type :: quantum_numbers_mask_t
204 generic
:: operator(.or
.) => quantum_numbers_mask_or
205 procedure
, private
:: quantum_numbers_mask_or
206 end type quantum_numbers_mask_t
209 integer, dimension(:), allocatable
:: entry
212 logical, dimension(:), allocatable
:: entry
214 type :: qn_mask_array_t
215 type(quantum_numbers_mask_t
), dimension(:), allocatable
:: mask
216 end type qn_mask_array_t
219 elemental
function quantum_numbers_mask_or (mask1
, mask2
) result (mask
)
220 type(quantum_numbers_mask_t
) :: mask
221 class(quantum_numbers_mask_t
), intent(in
) :: mask1
, mask2
222 end function quantum_numbers_mask_or
224 subroutine make_product_interaction
&
225 (prt_is_connected
, qn_mask_in
, qn_mask_rest
)
226 type(prt_mask_t
), dimension(2), intent(in
) :: prt_is_connected
227 type(qn_mask_array_t
), dimension(2), intent(in
) :: qn_mask_in
228 type(quantum_numbers_mask_t
), intent(in
) :: qn_mask_rest
229 type(index_map_t
), dimension(2) :: prt_index_in
231 type(quantum_numbers_mask_t
), dimension(:), allocatable
:: qn_mask
232 allocate (qn_mask (2))
234 qn_mask(prt_index_in(i
)%entry) = &
235 pack (qn_mask_in(i
)%mask
, prt_is_connected(i
)%entry) &
237 ! Without the patch above line produced an ICE.
239 end subroutine make_product_interaction
240 end module evaluators
244 type(model_data_t
) :: model
245 call model
%init_sm_test()
247 call beam_2 (6, model
)