Merge branch 'orientationClass_with_negative_P' of magit1.mpie.de:damask/DAMASK into orientationClass_with_negative_P

This commit is contained in:
Philip Eisenlohr 2018-12-07 22:07:22 -05:00
commit eaf2c77903
7 changed files with 33 additions and 22 deletions

View File

@ -158,12 +158,12 @@ Post_AverageDown:
- master - master
- release - release
Post_General: #Post_General:
stage: postprocessing # stage: postprocessing
script: PostProcessing/test.py # script: PostProcessing/test.py
except: # except:
- master # - master
- release # - release
Post_GeometryReconstruction: Post_GeometryReconstruction:
stage: postprocessing stage: postprocessing

View File

@ -244,7 +244,7 @@ for name in filenames:
continue continue
damask.util.report(scriptName,name) damask.util.report(scriptName,name)
randomSeed = int(os.urandom(4).encode('hex'), 16) if options.randomSeed is None else options.randomSeed # random seed per file for second phase randomSeed = int(os.urandom(4).hex(), 16) if options.randomSeed is None else options.randomSeed # random seed per file for second phase
random.seed(randomSeed) random.seed(randomSeed)
# ------------------------------------------ read header and data --------------------------------- # ------------------------------------------ read header and data ---------------------------------

View File

@ -191,7 +191,9 @@ recursive function IO_recursiveRead(fileName,cnt) result(fileContent)
l,i, & l,i, &
myStat myStat
if (merge(cnt,0_pInt,present(cnt))>10_pInt) call IO_error(106_pInt,ext_msg=trim(fileName)) if (present(cnt)) then
if (cnt>10_pInt) call IO_error(106_pInt,ext_msg=trim(fileName))
endif
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! read data as stream ! read data as stream
@ -684,7 +686,11 @@ function IO_stringValue(string,chunkPos,myChunk,silent)
logical :: warn logical :: warn
warn = merge(silent,.false.,present(silent)) if (present(silent)) then
warn = silent
else
warn = .false.
endif
IO_stringValue = '' IO_stringValue = ''
valuePresent: if (myChunk > chunkPos(1) .or. myChunk < 1_pInt) then valuePresent: if (myChunk > chunkPos(1) .or. myChunk < 1_pInt) then

View File

@ -513,8 +513,12 @@ character(len=65536) function getString(this,key,defaultVal,raw)
type(tPartitionedStringList), pointer :: item type(tPartitionedStringList), pointer :: item
logical :: found, & logical :: found, &
whole whole
if (present(raw)) then
whole = raw
else
whole = .false.
endif
whole = merge(raw,.false.,present(raw)) ! whole string or white space splitting
found = present(defaultVal) found = present(defaultVal)
if (found) then if (found) then
getString = trim(defaultVal) getString = trim(defaultVal)
@ -661,7 +665,11 @@ function getStrings(this,key,defaultVal,requiredShape,raw)
cumulative cumulative
cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')') cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')')
whole = merge(raw,.false.,present(raw)) if (present(raw)) then
whole = raw
else
whole = .false.
endif
found = .false. found = .false.
item => this item => this

View File

@ -225,7 +225,7 @@ subroutine kinematics_thermal_expansion_LiAndItsTangent(Li, dLi_dTstar3333, ipc,
+ lattice_thermalExpansion33(1:3,1:3,2,phase)*(T - TRef)**1 & ! linear coefficient + lattice_thermalExpansion33(1:3,1:3,2,phase)*(T - TRef)**1 & ! linear coefficient
+ lattice_thermalExpansion33(1:3,1:3,3,phase)*(T - TRef)**2 & ! quadratic coefficient + lattice_thermalExpansion33(1:3,1:3,3,phase)*(T - TRef)**2 & ! quadratic coefficient
) / & ) / &
(1.0_pReal \ (1.0_pReal &
+ lattice_thermalExpansion33(1:3,1:3,1,phase)*(T - TRef)**1 / 1. & + lattice_thermalExpansion33(1:3,1:3,1,phase)*(T - TRef)**1 / 1. &
+ lattice_thermalExpansion33(1:3,1:3,2,phase)*(T - TRef)**2 / 2. & + lattice_thermalExpansion33(1:3,1:3,2,phase)*(T - TRef)**2 / 2. &
+ lattice_thermalExpansion33(1:3,1:3,3,phase)*(T - TRef)**3 / 3. & + lattice_thermalExpansion33(1:3,1:3,3,phase)*(T - TRef)**3 / 3. &

View File

@ -302,7 +302,7 @@ subroutine math_check
endif endif
end subroutine math_check end subroutine math_check
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief Quicksort algorithm for two-dimensional integer arrays !> @brief Quicksort algorithm for two-dimensional integer arrays
@ -2625,12 +2625,9 @@ real(pReal) pure function math_clip(a, left, right)
real(pReal), intent(in) :: a real(pReal), intent(in) :: a
real(pReal), intent(in), optional :: left, right real(pReal), intent(in), optional :: left, right
math_clip = a
math_clip = min ( & if (present(left)) math_clip = max(left,math_clip)
max (merge(left, -huge(a), present(left)), a), & if (present(right)) math_clip = min(right,math_clip)
merge(right, huge(a), present(right)) &
)
if (present(left) .and. present(right)) & if (present(left) .and. present(right)) &
math_clip = merge (IEEE_value(1.0_pReal,IEEE_quiet_NaN),math_clip, left>right) math_clip = merge (IEEE_value(1.0_pReal,IEEE_quiet_NaN),math_clip, left>right)

View File

@ -120,8 +120,8 @@ subroutine spectral_damage_init()
trim(snes_type) == 'vinewtonssls') then trim(snes_type) == 'vinewtonssls') then
call DMGetGlobalVector(damage_grid,lBound,ierr); CHKERRQ(ierr) call DMGetGlobalVector(damage_grid,lBound,ierr); CHKERRQ(ierr)
call DMGetGlobalVector(damage_grid,uBound,ierr); CHKERRQ(ierr) call DMGetGlobalVector(damage_grid,uBound,ierr); CHKERRQ(ierr)
call VecSet(lBound,0.0,ierr); CHKERRQ(ierr) call VecSet(lBound,0.0_pReal,ierr); CHKERRQ(ierr)
call VecSet(uBound,1.0,ierr); CHKERRQ(ierr) call VecSet(uBound,1.0_pReal,ierr); CHKERRQ(ierr)
call SNESVISetVariableBounds(damage_snes,lBound,uBound,ierr) !< variable bounds for variational inequalities like contact mechanics, damage etc. call SNESVISetVariableBounds(damage_snes,lBound,uBound,ierr) !< variable bounds for variational inequalities like contact mechanics, damage etc.
call DMRestoreGlobalVector(damage_grid,lBound,ierr); CHKERRQ(ierr) call DMRestoreGlobalVector(damage_grid,lBound,ierr); CHKERRQ(ierr)
call DMRestoreGlobalVector(damage_grid,uBound,ierr); CHKERRQ(ierr) call DMRestoreGlobalVector(damage_grid,uBound,ierr); CHKERRQ(ierr)
@ -134,7 +134,7 @@ subroutine spectral_damage_init()
xend = xstart + xend - 1 xend = xstart + xend - 1
yend = ystart + yend - 1 yend = ystart + yend - 1
zend = zstart + zend - 1 zend = zstart + zend - 1
call VecSet(solution,1.0,ierr); CHKERRQ(ierr) call VecSet(solution,1.0_pReal,ierr); CHKERRQ(ierr)
allocate(damage_current(grid(1),grid(2),grid3), source=1.0_pReal) allocate(damage_current(grid(1),grid(2),grid3), source=1.0_pReal)
allocate(damage_lastInc(grid(1),grid(2),grid3), source=1.0_pReal) allocate(damage_lastInc(grid(1),grid(2),grid3), source=1.0_pReal)
allocate(damage_stagInc(grid(1),grid(2),grid3), source=1.0_pReal) allocate(damage_stagInc(grid(1),grid(2),grid3), source=1.0_pReal)