recursive SUBROUTINE em_field_custom(ele, param, s_rel, t_rel, orb, local_ref, field, calcd, err_flag, & calc_potential, use_overlap, grid_allow_s_out_of_bounds, rf_time, used_eles) USE bmad_struct USE bmad_interface, except_dummy => em_field_custom use em_field_interface IMPLICIT NONE type(ele_struct) :: ele type(lat_param_struct) param type(coord_struct) orb type(em_field_struct) field type (ele_pointer_struct), allocatable, optional :: used_eles(:) real(rp), intent(in) :: s_rel, t_rel logical out_of_range,local_ref logical first/.true./ logical, optional :: calcd, err_flag, calc_potential, grid_allow_s_out_of_bounds, use_overlap character(32) :: r_name = 'em_field_custom' !R = 3.094353005E9/(c_light/1.e9 * B) !B = 3.094353005*1.E9/(c_light*R) !E = B*c = 3.094353005*1.E9/(R)= ! E = 0.435089*1.e9 = 435 MV/m field%E = [ ele%value(custom_attribute1$),0.0_rp, 0.0_rp ] field%B = [ 0.0_rp, ele%value(custom_attribute2$), 0.0_rp ] !print '(a,3es12.4, 1x,6es12.4)',ele%name,field%E, orb%vec if(first)then print '(a,3es12.4)','field%E',field%E print '(a,3es12.4)','field%B',field%B first=.false. endif RETURN END SUBROUTINE em_field_custom