gibuu is hosted by Hepforge, IPPP Durham
GiBUU

TABLE OF CONTENTS


/VolumeElements [ Modules ]

[ Top ] [ Modules ]

NAME

module VolumeElements

PURPOSE

This module defines all stuff necessary to seperate the whole interaction volume in different "volume elements" (also called "VE-cells")

This is necessary for the implementation of "local ensemble" runs.

INPUTS

(none)


VolumeElements/tVolumeElements [ Types ]

[ Top ] [ VolumeElements ] [ Types ]

PURPOSE

Discretize the whole possible space volume and hold in a 3D array Lists of particles, which are at the moment in a given coordinate cell

NOTES

Die Arrays "zCoordFilled_xxx" sollen eine Abkürzung für die Loops über die z-Koordinate darstellen: Wenn für eine z-Koordinate für keine x- oder y-Zelle Einträge vorhanden sind, dann kann man diese z-Koord auch ganz schnell überspringen!

Denkbar wäre auch eine Verbesserung durch die Einführung von

   integer, dimension(3,2) :: iRange_Used

wobei alle Schleifen statt über

   iRange(i,1)..iRange(i,2)

über

   iRange_Used(i,1)..iRange_Used(i,2)

laufen würden. Hierbei können aber nur zusammenhängende Bereiche benutzt werden, wodurch das benutzte Modell wiederum starken Auftrieb bekommt!!!

SOURCE

  type tVolumeElements
     type(tParticleList), DIMENSION(:,:,:), ALLOCATABLE :: VE_real ! ~ 100 MB
     type(tParticleList), DIMENSION(:,:,:), ALLOCATABLE :: VE_pert ! ~ 100 MB
     real, dimension(3)      :: Delta
     real, dimension(3,2)    :: Range
     integer, dimension(3,2) :: iRange
     logical, dimension(:), ALLOCATABLE :: zCoordFilled_real
     logical, dimension(:), ALLOCATABLE :: zCoordFilled_pert
  end type tVolumeElements

VolumeElements/tVE [ Global module-variables ]

[ Top ] [ VolumeElements ] [ Global module-variables ]

PURPOSE

The one and only instance of a tVolumeElements-object

SOURCE

  type(tVolumeElements),save :: tVE

VolumeElements/VolumeElements_boxSize [ Functions ]

[ Top ] [ VolumeElements ] [ Functions ]

PURPOSE

Returns size of box used for the local ensemble method, unit of fm^3

OUTPUT

(function value)


VolumeElements/VolumeElements_INIT [ Subroutines ]

[ Top ] [ VolumeElements ] [ Subroutines ]

NAME

subroutine VolumeElements_INIT()

PURPOSE

This routine initializes the tVE-instance. Initial sizes are set and all memory allocation is done.

NOTES

The maximum volume size and also the volume elements size is still hard wired. maybe some more sophisticated init should be realized.


VolumeElements/VolumeElements_CLEAR [ Subroutines ]

[ Top ] [ VolumeElements ] [ Subroutines ]

NAME

subroutine VolumeElements_CLEAR()

PURPOSE

This routine resets the tVE-instance.


VolumeElements/VolumeElements_SETUP_Pert [ Subroutines ]

[ Top ] [ VolumeElements ] [ Subroutines ]

NAME

subroutine VolumeElements_SETUP_Pert(PartVec)

PURPOSE

Build up the tVE structure of perturbative particles.


VolumeElements/VolumeElements_SETUP_Real [ Subroutines ]

[ Top ] [ VolumeElements ] [ Subroutines ]

NAME

subroutine VolumeElements_SETUP_Real(PartVec)

PURPOSE

Build up the tVE structure of real particles.


VolumeElements/VolumeElements_Statistics [ Subroutines ]

[ Top ] [ VolumeElements ] [ Subroutines ]

NAME

subroutine VolumeElements_Statistics

PURPOSE

This is a routine to produce some statistical informations about the elements in the tVE instance.

This routine is only for trial/documentational purposes.


VolumeElements/FindNextVE [ Functions ]

[ Top ] [ VolumeElements ] [ Functions ]

NAME

logical function FindNextVE

PURPOSE

This routine searches for the next volume element with non-vanishing number of real- and perturbative-test-particles. It remembers the values of the last call and finds really the "next" cell.

It proceeds via first increasing the x- and y-coordinates and then stepping to the next z-coordinate.

INPUTS

  • the static stored array iPart(1:3)

OUTPUT

  • the static stored array iPart(1:3) (changed!)
  • function value: .false. -> no more tVE-cells possible


VolumeElements/VolumeElements_InitGetPart [ Subroutines ]

[ Top ] [ VolumeElements ] [ Subroutines ]

NAME

subroutine VolumeElements_InitGetPart

PURPOSE

initialize the "GetPart"-routines

NOTES

this routine sets the x-,y-,z-indizes in such a way, that a call to "FindNextVE" will start at the very first cell.


VolumeElements/VolumeElements_GetPart [ Functions ]

[ Top ] [ VolumeElements ] [ Functions ]

NAME

logical function VolumeElements_GetPart(Part1, Part2, nRealPart, iEns,iInd)

INPUTS

OUTPUT

PURPOSE

This routine finds the next (possibly colliding?) pair of one perturbative particle and one real particle in the actual VE-cell.

If one stepped over all pert. particles in thi given VE-cell, the next cell s choosen (cf. FindNextVE) and everything goes on.

If no "next VE-cell" is possible any more, the routine returns .false. as failure-indicator. (Otherwise always .true. is returned.)

NOTES

  • actually for a choosen VE-cell it returns the particle pairs (P_1,R_1), (P_2,R_2), ... (P_nPert, R_xxx) If there are more real particles than pert particles, "R_xxx" stands for "R_nPert". Otherwise, ie. if we have more pert particles than real particles, the loop restarts for the real particles (P_nReal,R_nReal), (P_nReal+1,R_1), ...

* random selection of access is not implemented yet.

   one should check whether ist really necessary !
   (maybe the insertion into different tVE-cells offers already
   enough random choice into the whole game)


VolumeElements/VolumeElements_NukSearch [ Subroutines ]

[ Top ] [ VolumeElements ] [ Subroutines ]

NAME

subroutine VolumeElements_NukSearch(partIn,RadiusNukSearch,proton1,proton2,neutron1,neutron2,FlagOK)

PURPOSE

This routine searches for two protons and two neutrons given in the "volume elements particle vector array" "VE_real" in the vicinty of the particle given by "partIn".

NOTES

we are looking for 2 protons and 2 neutrons, i.e. for 4 nucleons, while only 2 nucleons are necessary: possible combinations are p+p, p+n, n+n.

INPUTS

  • type(particle) :: partIn
  • real :: RadiusNukSearch

OUTPUT

  • type(particle), pointer :: proton1,proton2 -- Closest protons
  • type(particle), pointer :: neutron1,neutron2 -- Closest neutrons
  • logical :: FlagOK