made doxygen working for MSC.Marc again, small changes on the todo-statements for doxygen, they don't work on single lines of codes but only on module/variables

This commit is contained in:
Martin Diehl 2013-06-11 16:35:04 +00:00
parent ad314a60c0
commit 6f7740a243
8 changed files with 37 additions and 29 deletions

View File

@ -508,8 +508,8 @@ program DAMASK_spectral_Driver
write(6,'(1/,a)') ' ... writing results to file ......................................'
write(resUnit) materialpoint_results ! write result to file
endif
if( loadCases(currentLoadCase)%restartFrequency > 0_pInt .and. &
mod(inc,loadCases(currentLoadCase)%restartFrequency) == 0_pInt) then ! at frequency of writing restart information set restart parameter for FEsolving (first call to CPFEM_general will write ToDo: true?)
if( loadCases(currentLoadCase)%restartFrequency > 0_pInt .and. & ! at frequency of writing restart information set restart parameter for FEsolving
mod(inc,loadCases(currentLoadCase)%restartFrequency) == 0_pInt) then ! ToDo first call to CPFEM_general will write?
restartWrite = .true.
lastRestartWritten = inc
endif

View File

@ -231,6 +231,7 @@ end subroutine DAMASK_interface_init
!--------------------------------------------------------------------------------------------------
!> @brief extract working directory from loadcase file possibly based on current working dir
!> @todo change working directory with call chdir(storeWorkingDirectory)?
!--------------------------------------------------------------------------------------------------
character(len=1024) function storeWorkingDirectory(workingDirectoryArg,geometryArg)
@ -267,7 +268,6 @@ character(len=1024) function storeWorkingDirectory(workingDirectoryArg,geometryA
endif
endif
storeWorkingDirectory = rectifyPath(storeWorkingDirectory)
!@ToDo change working directory with? call chdir(storeWorkingDirectory)
end function storeWorkingDirectory

View File

@ -44,7 +44,7 @@ module DAMASK_spectral_solverAL
!--------------------------------------------------------------------------------------------------
! derived types
type tSolutionParams !< @ToDo: use here the type definition for a full loadcase including mask
type tSolutionParams !< @todo use here the type definition for a full loadcase including mask
real(pReal), dimension(3,3) :: P_BC, rotation_BC
real(pReal) :: timeinc
real(pReal) :: temperature
@ -115,6 +115,7 @@ contains
!--------------------------------------------------------------------------------------------------
!> @brief allocates all neccessary fields and fills them with data, potentially from restart info
!> @todo use sourced allocation, e.g. allocate(Fdot,source = F_lastInc)
!--------------------------------------------------------------------------------------------------
subroutine AL_init(temperature)
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran >4.6 at the moment)
@ -171,7 +172,7 @@ subroutine AL_init(temperature)
allocate (P (3,3,grid(1),grid(2),grid(3)),source = 0.0_pReal)
!--------------------------------------------------------------------------------------------------
! allocate global fields
allocate (F_lastInc (3,3,grid(1),grid(2),grid(3)),source = 0.0_pReal) !< @Todo sourced allocation allocate(Fdot,source = F_lastInc)
allocate (F_lastInc (3,3,grid(1),grid(2),grid(3)),source = 0.0_pReal)
allocate (Fdot (3,3,grid(1),grid(2),grid(3)),source = 0.0_pReal)
allocate (F_tau_lastInc(3,3,grid(1),grid(2),grid(3)),source = 0.0_pReal)
allocate (F_tauDot (3,3,grid(1),grid(2),grid(3)),source = 0.0_pReal)

View File

@ -364,7 +364,7 @@ end subroutine utilities_updateGamma
!> In case of debugging the FFT, also one component of the tensor (specified by row and column)
!> is independetly transformed complex to complex and compared to the whole tensor transform
!--------------------------------------------------------------------------------------------------
subroutine utilities_FFTforward() !< @ToDo make row and column between randomly between 1 and 3
subroutine utilities_FFTforward()
use math
implicit none

View File

@ -22,6 +22,7 @@
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!> Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @brief triggering reading in of restart information when doing a restart
!> @todo Descriptions for public variables needed
!--------------------------------------------------------------------------------------------------
module FEsolving
use prec, only: &
@ -30,36 +31,36 @@ module FEsolving
implicit none
private
integer(pInt), public :: &
cycleCounter = 0_pInt, &
theInc = -1_pInt, &
restartInc = 1_pInt
integer(pInt), public :: & !< needs description
cycleCounter = 0_pInt, & !< needs description
theInc = -1_pInt, & !< needs description
restartInc = 1_pInt !< needs description
real(pReal), public :: &
theTime = 0.0_pReal, &
theDelta = 0.0_pReal
theTime = 0.0_pReal, & !< needs description
theDelta = 0.0_pReal !< needs description
logical, public :: &
outdatedFFN1 = .false., & !< toDo
outdatedFFN1 = .false., & !< needs description
symmetricSolver = .false., & !< use a symmetric solver (FEM)
restartWrite = .false., & !< write current state to enable restart
restartRead = .false., & !< restart information to continue calculation from saved state
terminallyIll = .false., & !< at least one material point is terminally ill
lastMode = .true., & !< toDo
lastIncConverged = .false., & !< toDo
outdatedByNewInc = .false. !< toDo
lastMode = .true., & !< needs description
lastIncConverged = .false., & !< needs description
outdatedByNewInc = .false. !< needs description
integer(pInt), dimension(:,:), allocatable, public :: &
FEsolving_execIP
FEsolving_execIP !< needs description
integer(pInt), dimension(2), public :: &
FEsolving_execElem
FEsolving_execElem !< needs description
character(len=1024), public :: &
modelName
modelName !< needs description
logical, dimension(:,:), allocatable, public :: &
calcMode
calcMode !< needs description
public :: FE_init

View File

@ -3050,8 +3050,14 @@ logical function crystallite_integrateStress(&
tock, &
tickrate, &
maxticks
external :: dgesv
#if(FLOAT==8)
external :: &
dgesv
#elif(FLOAT==4)
external :: &
sgesv
#endif
!* be pessimistic
crystallite_integrateStress = .false.

View File

@ -20,7 +20,7 @@
!* $Id$
!--------------------------------------------------------------------------------------------------
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!! Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Parses material config file, either solverJobName.materialConfig or material.config
!> @details reads the material configuration file, where solverJobName.materialConfig takes
!! precedence over material.config and parses the sections 'homogenization', 'crystallite',
@ -1008,7 +1008,6 @@ subroutine material_populateGrains
enddo
enddo texture
!< @todo calc fraction after weighing with volumePerGrain, exchange in MC steps to improve result (humbug at the moment)
@ -1080,7 +1079,7 @@ subroutine material_populateGrains
deallocate(textureOfGrain)
deallocate(orientationOfGrain)
deallocate(Nelems)
!>@ToDo - causing segmentation fault: needs looking into
!> @todo - causing segmentation fault: needs looking into
!do homog = 1,material_Nhomogenization
! do micro = 1,material_Nmicrostructure
! if (Nelems(homog,micro) > 0_pInt) deallocate(elemsOfHomogMicro(homog,micro)%p)

View File

@ -1242,6 +1242,7 @@ end subroutine mesh_spectral_build_nodes
!--------------------------------------------------------------------------------------------------
!> @brief Store FEid, type, material, texture, and node list per element.
!! Allocates global array 'mesh_element'
!> @todo does the IO_error makes sense?
!--------------------------------------------------------------------------------------------------
subroutine mesh_spectral_build_elements(myUnit)
@ -1321,7 +1322,7 @@ subroutine mesh_spectral_build_elements(myUnit)
mesh_element( 3,e) = homog ! homogenization
mesh_element( 4,e) = microstructures(1_pInt+i) ! microstructure
mesh_element( 5,e) = e + (e-1_pInt)/grid(1) + &
((e-1_pInt)/(grid(1)*grid(2)))*(grid(1)+1_pInt) ! base node
((e-1_pInt)/(grid(1)*grid(2)))*(grid(1)+1_pInt) ! base node
mesh_element( 6,e) = mesh_element(5,e) + 1_pInt
mesh_element( 7,e) = mesh_element(5,e) + grid(1) + 2_pInt
mesh_element( 8,e) = mesh_element(5,e) + grid(1) + 1_pInt
@ -1329,13 +1330,13 @@ subroutine mesh_spectral_build_elements(myUnit)
mesh_element(10,e) = mesh_element(9,e) + 1_pInt
mesh_element(11,e) = mesh_element(9,e) + grid(1) + 2_pInt
mesh_element(12,e) = mesh_element(9,e) + grid(1) + 1_pInt
mesh_maxValStateVar(1) = max(mesh_maxValStateVar(1),mesh_element(3,e)) !needed for statistics
mesh_maxValStateVar(1) = max(mesh_maxValStateVar(1),mesh_element(3,e)) ! needed for statistics
mesh_maxValStateVar(2) = max(mesh_maxValStateVar(2),mesh_element(4,e))
enddo
enddo
deallocate(microstructures)
if (e /= mesh_NcpElems) call IO_error(880_pInt,e) !@ToDo does that make sense?
if (e /= mesh_NcpElems) call IO_error(880_pInt,e)
end subroutine mesh_spectral_build_elements