25  use, 
intrinsic :: iso_fortran_env
 
   50    integer, 
public :: ndim
 
   53    integer, 
public :: ntype_of_particle
 
   55    integer :: max_particles_per_type
 
   57    integer, 
public :: nparticle = 0
 
   59    integer :: ndensities_to_calculate
 
   68    character(80), 
allocatable :: labels_particles(:)
 
   70    integer, 
allocatable, 
public :: particletype(:)
 
   71    integer, 
allocatable, 
public :: nparticles_per_type(:)
 
   72    integer, 
allocatable, 
public :: particles_of_type(:,:)
 
   73    integer, 
allocatable, 
public :: bosonfermion(:)
 
   75    integer, 
allocatable :: exchange_symmetry(:,:,:)
 
   77    real(real64), 
allocatable :: mass_particle(:)
 
   79    real(real64), 
allocatable, 
public :: charge_particle(:)
 
   88    character(80), 
allocatable :: labels_densities(:)
 
   90    integer, 
allocatable :: particle_kept_densities(:)
 
  100    type(modelmb_particle_t), 
intent(inout) :: this
 
  101    type(namespace_t),        
intent(in)    :: namespace
 
  102    class(space_t),           
intent(in)    :: space
 
  104    integer :: ipart, ncols, nline, itmp, jtmp, npar, ntype
 
  119    call parse_variable(namespace, 
'NParticleModelmb', 0, this%nparticle)
 
  121    if (this%nparticle == 0) 
then 
  147    call parse_variable(namespace, 
'NTypeParticleModelmb', 1, this%ntype_of_particle)
 
  149    if (this%ntype_of_particle > this%nparticle) 
then 
  150      write (
message(1), 
'(2a,2I6)') 
' Number of types of modelmb particles should be <= Number of modelmb particles ', &
 
  151        this%ntype_of_particle, this%nparticle
 
  155    if (this%ndim*this%nparticle /= space%dim) 
then 
  156      message(1) = 
' Number of modelmb particles * dimension of modelmb space must be = Ndim' 
  191    npar = this%nparticle
 
  192    ntype = this%ntype_of_particle
 
  193    safe_allocate(this%labels_particles(1:npar))
 
  194    safe_allocate(this%particletype(1:npar))
 
  195    safe_allocate(this%mass_particle(1:npar))
 
  196    safe_allocate(this%charge_particle(1:npar))
 
  197    safe_allocate(this%bosonfermion(1:npar))
 
  198    safe_allocate(this%nparticles_per_type(1:ntype))
 
  199    safe_allocate(this%particles_of_type(1:npar, 1:ntype))
 
  202    this%labels_particles = 
'electron' 
  203    this%particletype = 1
 
  204    this%mass_particle = 
m_one 
  205    this%charge_particle = 
m_one 
  206    this%bosonfermion = 1 
 
  209    if (
parse_block(namespace, 
'DescribeParticlesModelmb', blk) == 0) 
then 
  218      if (nline /= this%nparticle) 
then 
  222      do ipart = 1, this%nparticle
 
  229        write (
message(1),
'(a,a)') 
'labels_particles = ', this%labels_particles(ipart)
 
  230        write (
message(2),
'(a,i6)') 
'particletype = ', this%particletype(ipart)
 
  231        write (
message(3),
'(a,E20.10)') 
'mass_particle = ', this%mass_particle(ipart)
 
  232        write (
message(4),
'(a,E20.10)') 
'charge_particle = ', this%charge_particle(ipart)
 
  233        write (
message(5),
'(a,i6)') 
'bosonfermion = ', this%bosonfermion(ipart)
 
  240    this%nparticles_per_type = 0
 
  241    this%particles_of_type = 0
 
  242    do ipart = 1, this%nparticle
 
  243      this%nparticles_per_type(this%particletype(ipart)) = &
 
  244        this%nparticles_per_type(this%particletype(ipart)) + 1
 
  245      this%particles_of_type(this%nparticles_per_type(this%particletype(ipart)), &
 
  246        this%particletype(ipart)) = ipart
 
  249    this%max_particles_per_type = maxval(this%nparticles_per_type)
 
  250    itmp = this%max_particles_per_type
 
  251    jtmp = this%ntype_of_particle
 
  252    safe_allocate(this%exchange_symmetry(1:itmp, 1:itmp, 1:jtmp))
 
  253    this%exchange_symmetry = 0
 
  265    safe_deallocate_a(this%labels_particles)
 
  266    safe_deallocate_a(this%particletype)
 
  267    safe_deallocate_a(this%mass_particle)
 
  268    safe_deallocate_a(this%charge_particle)
 
  269    safe_deallocate_a(this%nparticles_per_type)
 
  270    safe_deallocate_a(this%particles_of_type)
 
  271    safe_deallocate_a(this%exchange_symmetry)
 
  272    safe_deallocate_a(this%bosonfermion)
 
  274    safe_deallocate_a(this%labels_densities)
 
  275    safe_deallocate_a(this%particle_kept_densities)
 
  288    modelmb_out%ndim = modelmb_in%ndim
 
  289    modelmb_out%ntype_of_particle = modelmb_in%ntype_of_particle
 
  290    modelmb_out%max_particles_per_type = modelmb_in%max_particles_per_type
 
  291    modelmb_out%nparticle = modelmb_in%nparticle
 
  292    modelmb_out%ndensities_to_calculate = modelmb_in%ndensities_to_calculate
 
  294    safe_allocate_source_a(modelmb_out%labels_particles,modelmb_in%labels_particles)
 
  295    safe_allocate_source_a(modelmb_out%particletype,modelmb_in%particletype)
 
  296    safe_allocate_source_a(modelmb_out%mass_particle,modelmb_in%mass_particle)
 
  297    safe_allocate_source_a(modelmb_out%charge_particle,modelmb_in%charge_particle)
 
  298    safe_allocate_source_a(modelmb_out%nparticles_per_type,modelmb_in%nparticles_per_type)
 
  299    safe_allocate_source_a(modelmb_out%particles_of_type,modelmb_in%particles_of_type)
 
  300    safe_allocate_source_a(modelmb_out%exchange_symmetry,modelmb_in%exchange_symmetry)
 
  301    safe_allocate_source_a(modelmb_out%bosonfermion,modelmb_in%bosonfermion)
 
  303    safe_allocate_source_a(modelmb_out%labels_densities,modelmb_in%labels_densities)
 
  304    safe_allocate_source_a(modelmb_out%particle_kept_densities,modelmb_in%particle_kept_densities)
 
  314    real(real64),             
intent(inout) :: masses(:)
 
  316    integer :: dimcounter,ipart
 
  322    do ipart = 1,this%nparticle
 
  323      if (abs(this%mass_particle(ipart)-1.0_real64) > 1.e-10_real64) 
then 
  324        masses(dimcounter+1:dimcounter+this%ndim) = this%mass_particle(ipart)
 
  326      dimcounter = dimcounter+this%ndim
 
Prints out to iunit a message in the form: ["InputVariable" = value] where "InputVariable" is given b...
 
real(real64), parameter, public m_one
 
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
 
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
 
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
 
subroutine, public messages_input_error(namespace, var, details, row, column)
 
subroutine, public messages_experimental(name, namespace)
 
general module for modelmb particles
 
subroutine, public modelmb_copy_masses(this, masses)
==============================================================
 
subroutine, public modelmb_particles_end(this)
 
subroutine, public modelmb_particles_init(this, namespace, space)
==============================================================
 
subroutine, public modelmb_particles_copy(modelmb_out, modelmb_in)
 
integer function, public parse_block(namespace, name, blk, check_varinfo_)
 
==============================================================