Skip to content

Commit

Permalink
Merge branch 'feature.help.create.option.info' into 'master.dev'
Browse files Browse the repository at this point in the history
[feature.help.create.option.info] Added read-in parameter info [INT], [LOG], [REAL] etc. in --help output

See merge request piclas/piclas!663
  • Loading branch information
pnizenkov committed Jul 13, 2022
2 parents 4c96310 + d867e8f commit 58b1648
Show file tree
Hide file tree
Showing 12 changed files with 85 additions and 46 deletions.
2 changes: 1 addition & 1 deletion src/analyze/analyze.f90
Original file line number Diff line number Diff line change
Expand Up @@ -105,7 +105,7 @@ SUBROUTINE DefineParametersAnalyze()
!-- BoundaryFieldOutput
CALL prms%CreateLogicalOption( 'CalcBoundaryFieldOutput', 'Output the field boundary over time' , '.FALSE.')
CALL prms%CreateIntOption( 'BFO-NFieldBoundaries' , 'Number of boundaries used for CalcBoundaryFieldOutput')
CALL prms%CreateIntArrayOption( 'BFO-FieldBoundaries' , 'Vector (length BFO-NFieldBoundaries) with the numbers of each Field-Boundary')
CALL prms%CreateIntArrayOption( 'BFO-FieldBoundaries' , 'Vector (length BFO-NFieldBoundaries) with the numbers of each Field-Boundary', no=0)

!-- Poynting Vector
CALL prms%CreateIntOption( 'PoyntingVecInt-Planes', 'Total number of Poynting vector integral planes for measuring the '//&
Expand Down
6 changes: 3 additions & 3 deletions src/equations/poisson/equation.f90
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ SUBROUTINE DefineParametersEquation()
CALL prms%SetSection("Equation")
CALL prms%CreateIntOption( 'IniExactFunc' , 'TODO-DEFINE-PARAMETER\n'//&
'Define exact function necessary for linear scalar advection')
CALL prms%CreateRealArrayOption('RefState' , 'State(s) for electric potential (amplitude, frequency and phase shift).', multiple=.TRUE.)
CALL prms%CreateRealArrayOption('RefState' , 'State(s) for electric potential (amplitude, frequency and phase shift).', multiple=.TRUE., no=3)
CALL prms%CreateRealArrayOption('IniWavenumber' , 'TODO-DEFINE-PARAMETER' , '1. , 1. , 1.')
CALL prms%CreateRealArrayOption('IniCenter' , 'TODO-DEFINE-PARAMETER' , '0. , 0. , 0.')
CALL prms%CreateRealOption( 'IniAmplitude' , 'TODO-DEFINE-PARAMETER' , '0.1')
Expand All @@ -76,8 +76,8 @@ SUBROUTINE DefineParametersEquation()
'Modified for curved and shape-function influence (c*dt*SafetyFactor+r_cutoff)' , '1.0')

! Special BC with linear potential ramp (constant in time)
CALL prms%CreateRealArrayOption('LinPhiBasePoint' , 'Origin of coordinate system for linear potential ramp for BoundaryType = (/2,1/)' )
CALL prms%CreateRealArrayOption('LinPhiNormal' , 'Normal vector of coordinate system for linear potential ramp for BoundaryType = (/2,1/)' )
CALL prms%CreateRealArrayOption('LinPhiBasePoint' , 'Origin of coordinate system for linear potential ramp for BoundaryType = (/2,1/)' , no=3 )
CALL prms%CreateRealArrayOption('LinPhiNormal' , 'Normal vector of coordinate system for linear potential ramp for BoundaryType = (/2,1/)', no=3 )
CALL prms%CreateRealOption( 'LinPhiHeight' , 'Interval for ramping from 0 to LinPhi potential ramp for BoundaryType = (/2,1/)' )
CALL prms%CreateRealOption( 'LinPhi' , 'Target potential value for ramping from 0 for BoundaryType = (/2,1/)' )

Expand Down
2 changes: 1 addition & 1 deletion src/mesh/mesh.f90
Original file line number Diff line number Diff line change
Expand Up @@ -87,7 +87,7 @@ SUBROUTINE DefineParametersMesh()
"For each BoundaryName a BoundaryType needs to be specified.",&
multiple=.TRUE.)
CALL prms%CreateIntArrayOption('BoundaryType', "Type of boundary conditions to be set. Format: (BC_TYPE,BC_STATE)",&
multiple=.TRUE.)
multiple=.TRUE., no=2)
CALL prms%CreateLogicalOption( 'writePartitionInfo', "Write information about MPI partitions into a file.",'.FALSE.')

END SUBROUTINE DefineParametersMesh
Expand Down
6 changes: 3 additions & 3 deletions src/particles/dsmc/dsmc_bg_gas.f90
Original file line number Diff line number Diff line change
Expand Up @@ -50,9 +50,9 @@ SUBROUTINE DefineParametersBGG()
CALL prms%CreateStringOption( 'Particles-BGGas-Region[$]-Type' ,'Keyword for particle space condition of species [$] in case of multiple inits' , 'cylinder', numberedmulti=.TRUE.)
CALL prms%CreateRealOption( 'Particles-BGGas-Region[$]-RadiusIC' ,'Outer radius' , numberedmulti=.TRUE.)
CALL prms%CreateRealOption( 'Particles-BGGas-Region[$]-Radius2IC' ,'Inner radius (e.g. for a ring)' , '0.', numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('Particles-BGGas-Region[$]-BasePointIC' ,'Base point', numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('Particles-BGGas-Region[$]-BaseVector1IC' ,'First base vector', numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('Particles-BGGas-Region[$]-BaseVector2IC' ,'Second base vector', numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('Particles-BGGas-Region[$]-BasePointIC' , 'Base point' , numberedmulti=.TRUE., no=3)
CALL prms%CreateRealArrayOption('Particles-BGGas-Region[$]-BaseVector1IC' , 'First base vector' , numberedmulti=.TRUE., no=3)
CALL prms%CreateRealArrayOption('Particles-BGGas-Region[$]-BaseVector2IC' , 'Second base vector' , numberedmulti=.TRUE., no=3)
CALL prms%CreateRealOption( 'Particles-BGGas-Region[$]-CylinderHeightIC' ,'Third measure of cylinder', numberedmulti=.TRUE.)
END SUBROUTINE DefineParametersBGG

Expand Down
8 changes: 4 additions & 4 deletions src/particles/dsmc/dsmc_chemical_init.f90
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ SUBROUTINE DefineParametersChemistry()
'0', numberedmulti=.TRUE.)
CALL prms%CreateIntArrayOption( 'DSMC-Reaction[$]-NonReactiveSpecies' &
,'Array with the non-reactive collision partners for dissociation' &
,numberedmulti=.TRUE.)
,numberedmulti=.TRUE., no=0)
CALL prms%CreateStringOption( 'DSMC-Reaction[$]-ReactionModel' &
,'Used reaction model\n'//&
'TCE: Total Collision Energy\n'//&
Expand All @@ -61,9 +61,9 @@ SUBROUTINE DefineParametersChemistry()
,'Reactants of Reaction[$]\n'//&
'(SpecNumOfReactant1,\n'//&
'SpecNumOfReactant2,\n'//&
'SpecNumOfReactant3)', numberedmulti=.TRUE.)
'SpecNumOfReactant3)', numberedmulti=.TRUE.,no=3)
CALL prms%CreateIntArrayOption( 'DSMC-Reaction[$]-Products' &
,'Products of Reaction[j] (Product1, Product2, Product3, Product 4)',numberedmulti=.TRUE.)
,'Products of Reaction[j] (Product1, Product2, Product3, Product 4)',numberedmulti=.TRUE., no=4)
CALL prms%CreateRealOption( 'DSMC-Reaction[$]-Arrhenius-Prefactor', &
'Prefactor A of the extended Arrhenius equation, k = A * T^b * EXP(-E_a/T), '//&
'Units: 1/s, m3/s, m6/s (depending on the type of the reaction)', '0.' , numberedmulti=.TRUE.)
Expand Down Expand Up @@ -99,7 +99,7 @@ SUBROUTINE DefineParametersChemistry()
CALL prms%CreateIntOption( 'Particles-Chemistry-NumDeleteProducts','Number of species, which should be deleted if they are '//&
'a product of chemical reactions', '0')
CALL prms%CreateIntArrayOption( 'Particles-Chemistry-DeleteProductsList','List of the species indices to be deleted if they are '//&
'a product of chemical reactions')
'a product of chemical reactions', no=0)

CALL prms%CreateRealOption( 'DSMC-Reaction[$]-CrossSection', &
'Photon-ionization cross-section for the reaction type phIon', numberedmulti=.TRUE.)
Expand Down
2 changes: 1 addition & 1 deletion src/particles/emission/particle_surface_flux_init.f90
Original file line number Diff line number Diff line change
Expand Up @@ -83,7 +83,7 @@ SUBROUTINE DefineParametersParticleSurfaceFlux()
numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('Part-Species[$]-Surfaceflux[$]-origin', &
'Origin of circular inflow on the surface, where the coordinates depend on the axialDir:\n' //&
'x (=1): (y,z); y (=2): (z,x); z (=3): (x,y)', numberedmulti=.TRUE.)
'x (=1): (y,z); y (=2): (z,x); z (=3): (x,y)', numberedmulti=.TRUE., no=2)
CALL prms%CreateRealOption( 'Part-Species[$]-Surfaceflux[$]-rmax', &
'Maximum radius of the circular inflow to define a circle (rmin undefined) or a ring (rmin ' //&
'defined)', '1e21', numberedmulti=.TRUE.)
Expand Down
2 changes: 1 addition & 1 deletion src/particles/particle_init.f90
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ SUBROUTINE DefineParametersParticles()
CALL prms%CreateIntOption( 'InitialIonizationSpecies', 'Supply the number of species that are considered for automatic '//&
'ionization')
CALL prms%CreateIntArrayOption( 'InitialIonizationSpeciesID', 'Supply a vector with the species IDs that are used for the '//&
'initial ionization.')
'initial ionization.',no=0)
CALL prms%CreateRealOption( 'InitialIonizationChargeAverage' , 'Average charge for each atom/molecule in the cell '//&
'(corresponds to the ionization degree)')

Expand Down
8 changes: 4 additions & 4 deletions src/particles/particle_timestep.f90
Original file line number Diff line number Diff line change
Expand Up @@ -72,11 +72,11 @@ SUBROUTINE DefineParametersVaribleTimeStep()
CALL prms%CreateRealArrayOption('Part-VariableTimeStep-Direction', &
'Direction of the vector along which a linear increase is applied to the time step. '//&
'Currently only scaling along the x-axis (positive or negative direction) is allowed, '//&
'e.g. (/-1.0,0.0,0.0/)')
'e.g. (/-1.0,0.0,0.0/)', no=3)
CALL prms%CreateRealArrayOption('Part-VariableTimeStep-StartPoint', &
'Starting point of the vector, to use the domain border: -99999.')
'Starting point of the vector, to use the domain border: -99999.',no=3)
CALL prms%CreateRealArrayOption('Part-VariableTimeStep-EndPoint' , &
'End point of the vector, to use the domain border: -99999.')
'End point of the vector, to use the domain border: -99999.', no=3)
! 2D/Axi: Radial and axial scaling towards
CALL prms%CreateLogicalOption('Part-VariableTimeStep-Use2DFunction', &
'Only 2D/Axi simulations: Enables the scaling of the time step in the x-direction towards and '//&
Expand Down Expand Up @@ -518,4 +518,4 @@ SUBROUTINE VarTimeStep_CalcElemFacs()

END SUBROUTINE VarTimeStep_CalcElemFacs

END MODULE MOD_Particle_VarTimeStep
END MODULE MOD_Particle_VarTimeStep
4 changes: 2 additions & 2 deletions src/particles/surfacemodel/surfacemodel_analyze.f90
Original file line number Diff line number Diff line change
Expand Up @@ -61,9 +61,9 @@ SUBROUTINE DefineParametersSurfModelAnalyze()
!-- BoundaryParticleOutput
CALL prms%CreateLogicalOption( 'CalcBoundaryParticleOutput', 'Count number of particles exiting for species X on boundary X' , '.FALSE.')
CALL prms%CreateIntOption( 'BPO-NPartBoundaries' , 'Number of boundaries used for CalcBoundaryParticleOutput')
CALL prms%CreateIntArrayOption( 'BPO-PartBoundaries' , 'Vector (length BPO-NPartBoundaries) with the numbers of each Part-Boundary')
CALL prms%CreateIntArrayOption( 'BPO-PartBoundaries' , 'Vector (length BPO-NPartBoundaries) with the numbers of each Part-Boundary', no=0)
CALL prms%CreateIntOption( 'BPO-NSpecies' , 'Number of species used for CalcBoundaryParticleOutput')
CALL prms%CreateIntArrayOption( 'BPO-Species' , 'Vector (length BPO-NSpecies) with the corresponding Species IDs')
CALL prms%CreateIntArrayOption( 'BPO-Species' , 'Vector (length BPO-NSpecies) with the corresponding Species IDs', no=0)
CALL prms%CreateLogicalOption( 'CalcElectronSEE' , 'Count the electron emission from BCs where SEE is active','.FALSE.')

END SUBROUTINE DefineParametersSurfModelAnalyze
Expand Down
2 changes: 1 addition & 1 deletion src/particles/surfacemodel/surfacemodel_porous.f90
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,7 @@ SUBROUTINE DefineParametersPorousBC()
, numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('Surf-PorousBC[$]-origin' &
, 'Coordinates of the middle point of the region, Example: normalDir=1: (/y,z/), ' //&
'normalDir=2: (/z,x/), normalDir=3: (/x,y/)', numberedmulti=.TRUE.)
'normalDir=2: (/z,x/), normalDir=3: (/x,y/)', numberedmulti=.TRUE., no=2)
CALL prms%CreateRealOption( 'Surf-PorousBC[$]-rmax' &
, 'Maximum radius [m] of the circular region', '1e21', numberedmulti=.TRUE.)
CALL prms%CreateRealOption( 'Surf-PorousBC[$]-rmin' &
Expand Down
24 changes: 12 additions & 12 deletions src/posti/superB/superB_init.f90
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ SUBROUTINE DefineParametersSuperB()
CALL prms%CreateStringOption( 'PermanentMagnet[$]-Type' , 'Permanent magnet type: cuboid, sphere, cylinder, conic', &
numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('PermanentMagnet[$]-BasePoint' , 'Origin (vector) for geometry parametrization', &
numberedmulti=.TRUE.)
numberedmulti=.TRUE., no=3)
CALL prms%CreateIntOption( 'PermanentMagnet[$]-NumNodes' , 'Number of Gauss points for the discretization of the '//&
'permanent magnet:\n'//&
'Cuboid: N points in each direction (total number: 6N^2)\n'//&
Expand All @@ -57,26 +57,26 @@ SUBROUTINE DefineParametersSuperB()
'the top and bottom face\n'//&
'Conic: see the cylinder NumNodes description', &
numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('PermanentMagnet[$]-Magnetisation' , 'Magnetisation vector in [A/m]', numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('PermanentMagnet[$]-BaseVector1' , 'Vector 1 spanning the cuboid', numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('PermanentMagnet[$]-BaseVector2' , 'Vector 2 spanning the cuboid', numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('PermanentMagnet[$]-BaseVector3' , 'Vector 3 spanning the cuboid', numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('PermanentMagnet[$]-Magnetisation' , 'Magnetisation vector in [A/m]', numberedmulti=.TRUE., no=3)
CALL prms%CreateRealArrayOption('PermanentMagnet[$]-BaseVector1' , 'Vector 1 spanning the cuboid', numberedmulti=.TRUE., no=3)
CALL prms%CreateRealArrayOption('PermanentMagnet[$]-BaseVector2' , 'Vector 2 spanning the cuboid', numberedmulti=.TRUE., no=3)
CALL prms%CreateRealArrayOption('PermanentMagnet[$]-BaseVector3' , 'Vector 3 spanning the cuboid', numberedmulti=.TRUE., no=3)
CALL prms%CreateRealOption( 'PermanentMagnet[$]-Radius' , 'Radius of a spheric, cylindric and conic (first radius) '//&
'permanent magnet', numberedmulti=.TRUE.)
CALL prms%CreateRealOption( 'PermanentMagnet[$]-Radius2' , 'Radius of the second radius of the conic permanent magnet'//&
' or inner radius for hollow cylinders', &
numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('PermanentMagnet[$]-HeightVector' , 'Height vector of cylindric and conic permanent magnet', &
numberedmulti=.TRUE.)
numberedmulti=.TRUE., no=3)

! Input of coils
CALL prms%SetSection('Input of coils')
CALL prms%CreateIntOption( 'NumOfCoils' , 'Number of coils','0')
CALL prms%CreateStringOption( 'Coil[$]-Type' , 'Coil type: custom, circle, rectangular, linear conductor (straight '//&
'wire)', numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('Coil[$]-BasePoint' , 'Origin vector of the coil/linear conductor', numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('Coil[$]-BasePoint' , 'Origin vector of the coil/linear conductor', numberedmulti=.TRUE., no=3)
CALL prms%CreateRealArrayOption('Coil[$]-LengthVector' , 'Length vector of the coil/linear conductor, normal to the cross-'//&
'sectional area', numberedmulti=.TRUE.)
'sectional area', numberedmulti=.TRUE., no=3)
CALL prms%CreateRealOption( 'Coil[$]-Current' , 'Electrical coil current [A]', numberedmulti=.TRUE.)

! Linear conductor (calculated from the number of loops and points per loop for coils)
Expand All @@ -86,15 +86,15 @@ SUBROUTINE DefineParametersSuperB()
CALL prms%CreateIntOption( 'Coil[$]-LoopNum' , 'Number of coil loops', numberedmulti=.TRUE.)
CALL prms%CreateIntOption( 'Coil[$]-PointsPerLoop' , 'Number of points per loop (azimuthal discretization)', numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('Coil[$]-AxisVec1' , 'Axial vector defines the orientation of the cross-section together '//&
'with the length vector', numberedmulti=.TRUE.)
'with the length vector', numberedmulti=.TRUE., no=3)
! Custom coils
CALL prms%SetSection('Custom coils')
CALL prms%CreateIntOption( 'Coil[$]-NumOfSegments' , 'Number of segments for the custom coil definition', numberedmulti=.TRUE.)
CALL prms%CreateStringOption( 'Coil[$]-Segment[$]-SegmentType' , 'Possible segment types: line or circle', numberedmulti=.TRUE.)
CALL prms%CreateIntOption( 'Coil[$]-Segment[$]-NumOfPoints' , 'Number of points to discretize the segment', &
numberedmulti=.TRUE.)
CALL prms%CreateRealArrayOption('Coil[$]-Segment[$]-LineVector' , 'Line segment: Vector (x,y) in the cross-sectional plane '//&
'defined by the length and axial vector', numberedmulti=.TRUE.)
'defined by the length and axial vector', numberedmulti=.TRUE., no=2)
CALL prms%CreateRealOption( 'Coil[$]-Segment[$]-Radius' , 'Circle segment: Radius in the cross-sectional plane '//&
'defined by the length and axial vector', numberedmulti=.TRUE.)
CALL prms%CreateRealOption( 'Coil[$]-Segment[$]-Phi1' , 'Circle segment: Initial angle in [deg]', numberedmulti=.TRUE.)
Expand All @@ -105,9 +105,9 @@ SUBROUTINE DefineParametersSuperB()

! Rectangle coils
CALL prms%CreateRealArrayOption('Coil[$]-RectVec1' , 'Vector 1 (x,y) in the cross-sectional plane defined by the length '//&
'and axial vector, spanning the rectangular coil', numberedmulti=.TRUE.)
'and axial vector, spanning the rectangular coil', numberedmulti=.TRUE., no=2)
CALL prms%CreateRealArrayOption('Coil[$]-RectVec2' , 'Vector 2 (x,y) in the cross-sectional plane defined by the length '//&
'and axial vector, spanning the rectangular coil', numberedmulti=.TRUE.)
'and axial vector, spanning the rectangular coil', numberedmulti=.TRUE., no=2)

! Time-dependent coils
CALL prms%SetSection('Time-dependent coils')
Expand Down
Loading

0 comments on commit 58b1648

Please sign in to comment.