introduced homogenization_none to substitute isostrain with ngrains 1.
cleaned up homogenization isostrain (has no state)
This commit is contained in:
parent
670c0caabc
commit
5d4017bbfc
|
@ -108,6 +108,7 @@ end module DAMASK_interface
|
||||||
#include "constitutive_nonlocal.f90"
|
#include "constitutive_nonlocal.f90"
|
||||||
#include "constitutive.f90"
|
#include "constitutive.f90"
|
||||||
#include "crystallite.f90"
|
#include "crystallite.f90"
|
||||||
|
#include "homogenization_none.f90"
|
||||||
#include "homogenization_isostrain.f90"
|
#include "homogenization_isostrain.f90"
|
||||||
#include "homogenization_RGC.f90"
|
#include "homogenization_RGC.f90"
|
||||||
#include "homogenization.f90"
|
#include "homogenization.f90"
|
||||||
|
|
|
@ -108,6 +108,7 @@ end module DAMASK_interface
|
||||||
#include "constitutive_nonlocal.f90"
|
#include "constitutive_nonlocal.f90"
|
||||||
#include "constitutive.f90"
|
#include "constitutive.f90"
|
||||||
#include "crystallite.f90"
|
#include "crystallite.f90"
|
||||||
|
#include "homogenization_none.f90"
|
||||||
#include "homogenization_isostrain.f90"
|
#include "homogenization_isostrain.f90"
|
||||||
#include "homogenization_RGC.f90"
|
#include "homogenization_RGC.f90"
|
||||||
#include "homogenization.f90"
|
#include "homogenization.f90"
|
||||||
|
|
|
@ -137,6 +137,7 @@ end module DAMASK_interface
|
||||||
#include "constitutive_nonlocal.f90"
|
#include "constitutive_nonlocal.f90"
|
||||||
#include "constitutive.f90"
|
#include "constitutive.f90"
|
||||||
#include "crystallite.f90"
|
#include "crystallite.f90"
|
||||||
|
#include "homogenization_none.f90"
|
||||||
#include "homogenization_isostrain.f90"
|
#include "homogenization_isostrain.f90"
|
||||||
#include "homogenization_RGC.f90"
|
#include "homogenization_RGC.f90"
|
||||||
#include "homogenization.f90"
|
#include "homogenization.f90"
|
||||||
|
|
|
@ -344,7 +344,7 @@ COMPILED_FILES = prec.o DAMASK_spectral_interface.o IO.o libs.o numerics.o debug
|
||||||
FEsolving.o mesh.o material.o lattice.o \
|
FEsolving.o mesh.o material.o lattice.o \
|
||||||
constitutive_dislotwin.o constitutive_j2.o constitutive_phenopowerlaw.o \
|
constitutive_dislotwin.o constitutive_j2.o constitutive_phenopowerlaw.o \
|
||||||
constitutive_titanmod.o constitutive_nonlocal.o constitutive_none.o constitutive.o crystallite.o \
|
constitutive_titanmod.o constitutive_nonlocal.o constitutive_none.o constitutive.o crystallite.o \
|
||||||
homogenization_RGC.o homogenization_isostrain.o homogenization.o CPFEM.o \
|
homogenization_RGC.o homogenization_isostrain.o homogenization_none.o homogenization.o CPFEM.o \
|
||||||
DAMASK_spectral_utilities.o DAMASK_spectral_solverBasic.o
|
DAMASK_spectral_utilities.o DAMASK_spectral_solverBasic.o
|
||||||
|
|
||||||
ifdef PETSC_DIR
|
ifdef PETSC_DIR
|
||||||
|
@ -381,6 +381,7 @@ CPFEM.o: CPFEM.f90\
|
||||||
homogenization.o
|
homogenization.o
|
||||||
|
|
||||||
homogenization.o: homogenization.f90\
|
homogenization.o: homogenization.f90\
|
||||||
|
homogenization_none.o \
|
||||||
homogenization_RGC.o \
|
homogenization_RGC.o \
|
||||||
homogenization_isostrain.o
|
homogenization_isostrain.o
|
||||||
|
|
||||||
|
@ -390,6 +391,9 @@ homogenization_RGC.o: homogenization_RGC.f90 \
|
||||||
homogenization_isostrain.o: homogenization_isostrain.f90 \
|
homogenization_isostrain.o: homogenization_isostrain.f90 \
|
||||||
crystallite.o
|
crystallite.o
|
||||||
|
|
||||||
|
homogenization_none.o: homogenization_none.f90 \
|
||||||
|
crystallite.o
|
||||||
|
|
||||||
crystallite.o: crystallite.f90 \
|
crystallite.o: crystallite.f90 \
|
||||||
constitutive.o
|
constitutive.o
|
||||||
|
|
||||||
|
|
|
@ -126,6 +126,7 @@ subroutine homogenization_init()
|
||||||
use crystallite, only: &
|
use crystallite, only: &
|
||||||
crystallite_maxSizePostResults
|
crystallite_maxSizePostResults
|
||||||
use material
|
use material
|
||||||
|
use homogenization_none
|
||||||
use homogenization_isostrain
|
use homogenization_isostrain
|
||||||
use homogenization_RGC
|
use homogenization_RGC
|
||||||
|
|
||||||
|
@ -146,7 +147,11 @@ subroutine homogenization_init()
|
||||||
! parse homogenization from config file
|
! parse homogenization from config file
|
||||||
if (.not. IO_open_jobFile_stat(FILEUNIT,material_localFileExt)) & ! no local material configuration present...
|
if (.not. IO_open_jobFile_stat(FILEUNIT,material_localFileExt)) & ! no local material configuration present...
|
||||||
call IO_open_file(FILEUNIT,material_configFile) ! ... open material.config file
|
call IO_open_file(FILEUNIT,material_configFile) ! ... open material.config file
|
||||||
|
if (any(homogenization_type == HOMOGENIZATION_NONE_ID)) &
|
||||||
|
call homogenization_none_init(FILEUNIT)
|
||||||
|
if (any(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)) &
|
||||||
call homogenization_isostrain_init(FILEUNIT)
|
call homogenization_isostrain_init(FILEUNIT)
|
||||||
|
if (any(homogenization_type == HOMOGENIZATION_RGC_ID)) &
|
||||||
call homogenization_RGC_init(FILEUNIT)
|
call homogenization_RGC_init(FILEUNIT)
|
||||||
close(FILEUNIT)
|
close(FILEUNIT)
|
||||||
|
|
||||||
|
@ -157,6 +162,10 @@ subroutine homogenization_init()
|
||||||
i = homogenization_typeInstance(p) ! which instance of this homogenization type
|
i = homogenization_typeInstance(p) ! which instance of this homogenization type
|
||||||
knownHomogenization = .true. ! assume valid
|
knownHomogenization = .true. ! assume valid
|
||||||
select case(homogenization_type(p)) ! split per homogenization type
|
select case(homogenization_type(p)) ! split per homogenization type
|
||||||
|
case (HOMOGENIZATION_NONE_ID)
|
||||||
|
outputName = HOMOGENIZATION_NONE_label
|
||||||
|
thisOutput => null()
|
||||||
|
thisSize => null()
|
||||||
case (HOMOGENIZATION_ISOSTRAIN_ID)
|
case (HOMOGENIZATION_ISOSTRAIN_ID)
|
||||||
outputName = HOMOGENIZATION_ISOSTRAIN_label
|
outputName = HOMOGENIZATION_ISOSTRAIN_label
|
||||||
thisOutput => homogenization_isostrain_output
|
thisOutput => homogenization_isostrain_output
|
||||||
|
@ -212,14 +221,9 @@ subroutine homogenization_init()
|
||||||
mapping(e,1:4) = [instancePosition(myinstance),myinstance,e,i]
|
mapping(e,1:4) = [instancePosition(myinstance),myinstance,e,i]
|
||||||
#endif
|
#endif
|
||||||
select case(homogenization_type(mesh_element(3,e)))
|
select case(homogenization_type(mesh_element(3,e)))
|
||||||
|
case (HOMOGENIZATION_none_ID)
|
||||||
|
homogenization_sizePostResults(i,e) = 0_pInt
|
||||||
case (HOMOGENIZATION_ISOSTRAIN_ID)
|
case (HOMOGENIZATION_ISOSTRAIN_ID)
|
||||||
if (homogenization_isostrain_sizeState(myInstance) > 0_pInt) then
|
|
||||||
allocate(homogenization_state0(i,e)%p(homogenization_isostrain_sizeState(myInstance)))
|
|
||||||
allocate(homogenization_subState0(i,e)%p(homogenization_isostrain_sizeState(myInstance)))
|
|
||||||
allocate(homogenization_state(i,e)%p(homogenization_isostrain_sizeState(myInstance)))
|
|
||||||
homogenization_state0(i,e)%p = 0.0_pReal
|
|
||||||
homogenization_sizeState(i,e) = homogenization_isostrain_sizeState(myInstance)
|
|
||||||
endif
|
|
||||||
homogenization_sizePostResults(i,e) = homogenization_isostrain_sizePostResults(myInstance)
|
homogenization_sizePostResults(i,e) = homogenization_isostrain_sizePostResults(myInstance)
|
||||||
case (HOMOGENIZATION_RGC_ID)
|
case (HOMOGENIZATION_RGC_ID)
|
||||||
if (homogenization_RGC_sizeState(myInstance) > 0_pInt) then
|
if (homogenization_RGC_sizeState(myInstance) > 0_pInt) then
|
||||||
|
@ -654,6 +658,7 @@ subroutine homogenization_partitionDeformation(ip,el)
|
||||||
use material, only: &
|
use material, only: &
|
||||||
homogenization_type, &
|
homogenization_type, &
|
||||||
homogenization_maxNgrains, &
|
homogenization_maxNgrains, &
|
||||||
|
HOMOGENIZATION_NONE_ID, &
|
||||||
HOMOGENIZATION_ISOSTRAIN_ID, &
|
HOMOGENIZATION_ISOSTRAIN_ID, &
|
||||||
HOMOGENIZATION_RGC_ID
|
HOMOGENIZATION_RGC_ID
|
||||||
use crystallite, only: &
|
use crystallite, only: &
|
||||||
|
@ -670,6 +675,12 @@ subroutine homogenization_partitionDeformation(ip,el)
|
||||||
el !< element number
|
el !< element number
|
||||||
|
|
||||||
chosenHomogenization: select case(homogenization_type(mesh_element(3,el)))
|
chosenHomogenization: select case(homogenization_type(mesh_element(3,el)))
|
||||||
|
|
||||||
|
case (HOMOGENIZATION_NONE_ID) chosenHomogenization
|
||||||
|
crystallite_partionedF(1:3,1:3,1:homogenization_maxNgrains,ip,el) = 0.0_pReal
|
||||||
|
crystallite_partionedF(1:3,1:3,1:1,ip,el) = &
|
||||||
|
spread(materialpoint_subF(1:3,1:3,ip,el),3,1)
|
||||||
|
|
||||||
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
|
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
|
||||||
call homogenization_isostrain_partitionDeformation(&
|
call homogenization_isostrain_partitionDeformation(&
|
||||||
crystallite_partionedF(1:3,1:3,1:homogenization_maxNgrains,ip,el), &
|
crystallite_partionedF(1:3,1:3,1:homogenization_maxNgrains,ip,el), &
|
||||||
|
@ -742,6 +753,7 @@ subroutine homogenization_averageStressAndItsTangent(ip,el)
|
||||||
use material, only: &
|
use material, only: &
|
||||||
homogenization_type, &
|
homogenization_type, &
|
||||||
homogenization_maxNgrains, &
|
homogenization_maxNgrains, &
|
||||||
|
HOMOGENIZATION_NONE_ID, &
|
||||||
HOMOGENIZATION_ISOSTRAIN_ID, &
|
HOMOGENIZATION_ISOSTRAIN_ID, &
|
||||||
HOMOGENIZATION_RGC_ID
|
HOMOGENIZATION_RGC_ID
|
||||||
use crystallite, only: &
|
use crystallite, only: &
|
||||||
|
@ -757,6 +769,10 @@ subroutine homogenization_averageStressAndItsTangent(ip,el)
|
||||||
el !< element number
|
el !< element number
|
||||||
|
|
||||||
chosenHomogenization: select case(homogenization_type(mesh_element(3,el)))
|
chosenHomogenization: select case(homogenization_type(mesh_element(3,el)))
|
||||||
|
case (HOMOGENIZATION_NONE_ID) chosenHomogenization
|
||||||
|
materialpoint_P(1:3,1:3,ip,el) = sum(crystallite_P(1:3,1:3,1:1,ip,el),3)
|
||||||
|
materialpoint_dPdF(1:3,1:3,1:3,1:3,ip,el) &
|
||||||
|
= sum(crystallite_dPdF(1:3,1:3,1:3,1:3,1:1,ip,el),5)
|
||||||
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
|
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
|
||||||
call homogenization_isostrain_averageStressAndItsTangent(&
|
call homogenization_isostrain_averageStressAndItsTangent(&
|
||||||
materialpoint_P(1:3,1:3,ip,el), &
|
materialpoint_P(1:3,1:3,ip,el), &
|
||||||
|
@ -812,6 +828,7 @@ function homogenization_postResults(ip,el)
|
||||||
mesh_element
|
mesh_element
|
||||||
use material, only: &
|
use material, only: &
|
||||||
homogenization_type, &
|
homogenization_type, &
|
||||||
|
HOMOGENIZATION_NONE_ID, &
|
||||||
HOMOGENIZATION_ISOSTRAIN_ID, &
|
HOMOGENIZATION_ISOSTRAIN_ID, &
|
||||||
HOMOGENIZATION_RGC_ID
|
HOMOGENIZATION_RGC_ID
|
||||||
use homogenization_isostrain, only: &
|
use homogenization_isostrain, only: &
|
||||||
|
@ -827,6 +844,8 @@ function homogenization_postResults(ip,el)
|
||||||
|
|
||||||
homogenization_postResults = 0.0_pReal
|
homogenization_postResults = 0.0_pReal
|
||||||
chosenHomogenization: select case (homogenization_type(mesh_element(3,el)))
|
chosenHomogenization: select case (homogenization_type(mesh_element(3,el)))
|
||||||
|
case (HOMOGENIZATION_NONE_ID) chosenHomogenization
|
||||||
|
|
||||||
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
|
case (HOMOGENIZATION_ISOSTRAIN_ID) chosenHomogenization
|
||||||
homogenization_postResults = homogenization_isostrain_postResults(&
|
homogenization_postResults = homogenization_isostrain_postResults(&
|
||||||
ip, &
|
ip, &
|
||||||
|
|
|
@ -30,7 +30,6 @@ module homogenization_isostrain
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||||
homogenization_isostrain_sizeState, &
|
|
||||||
homogenization_isostrain_sizePostResults
|
homogenization_isostrain_sizePostResults
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||||
homogenization_isostrain_sizePostResult
|
homogenization_isostrain_sizePostResult
|
||||||
|
@ -70,9 +69,6 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine homogenization_isostrain_init(fileUnit)
|
subroutine homogenization_isostrain_init(fileUnit)
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
||||||
use math, only: &
|
|
||||||
math_Mandel3333to66, &
|
|
||||||
math_Voigt66to3333
|
|
||||||
use IO
|
use IO
|
||||||
use material
|
use material
|
||||||
|
|
||||||
|
@ -96,7 +92,6 @@ subroutine homogenization_isostrain_init(fileUnit)
|
||||||
maxNinstance = count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)
|
maxNinstance = count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)
|
||||||
if (maxNinstance == 0) return
|
if (maxNinstance == 0) return
|
||||||
|
|
||||||
allocate(homogenization_isostrain_sizeState(maxNinstance), source=0_pInt)
|
|
||||||
allocate(homogenization_isostrain_sizePostResults(maxNinstance), source=0_pInt)
|
allocate(homogenization_isostrain_sizePostResults(maxNinstance), source=0_pInt)
|
||||||
allocate(homogenization_isostrain_sizePostResult(maxval(homogenization_Noutput),maxNinstance), &
|
allocate(homogenization_isostrain_sizePostResult(maxval(homogenization_Noutput),maxNinstance), &
|
||||||
source=0_pInt)
|
source=0_pInt)
|
||||||
|
@ -168,7 +163,6 @@ subroutine homogenization_isostrain_init(fileUnit)
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
do k = 1,maxNinstance
|
do k = 1,maxNinstance
|
||||||
homogenization_isostrain_sizeState(i) = 0_pInt
|
|
||||||
|
|
||||||
do j = 1_pInt,maxval(homogenization_Noutput)
|
do j = 1_pInt,maxval(homogenization_Noutput)
|
||||||
select case(homogenization_isostrain_outputID(j,i))
|
select case(homogenization_isostrain_outputID(j,i))
|
||||||
|
|
|
@ -0,0 +1,61 @@
|
||||||
|
! Copyright 2011-13 Max-Planck-Institut für Eisenforschung GmbH
|
||||||
|
!
|
||||||
|
! This file is part of DAMASK,
|
||||||
|
! the Düsseldorf Advanced MAterial Simulation Kit.
|
||||||
|
!
|
||||||
|
! DAMASK is free software: you can redistribute it and/or modify
|
||||||
|
! it under the terms of the GNU General Public License as published by
|
||||||
|
! the Free Software Foundation, either version 3 of the License, or
|
||||||
|
! (at your option) any later version.
|
||||||
|
!
|
||||||
|
! DAMASK is distributed in the hope that it will be useful,
|
||||||
|
! but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||||
|
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||||
|
! GNU General Public License for more details.
|
||||||
|
!
|
||||||
|
! You should have received a copy of the GNU General Public License
|
||||||
|
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
|
||||||
|
!
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
! $Id$
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
|
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
|
!> @brief Isostrain (full constraint Taylor assuption) homogenization scheme
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
module homogenization_none
|
||||||
|
use prec, only: &
|
||||||
|
pInt
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
private
|
||||||
|
|
||||||
|
public :: &
|
||||||
|
homogenization_none_init
|
||||||
|
|
||||||
|
contains
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief allocates all neccessary fields, reads information from material configuration file
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
subroutine homogenization_none_init(fileUnit)
|
||||||
|
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
||||||
|
use IO
|
||||||
|
use material
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
integer(pInt), intent(in) :: fileUnit
|
||||||
|
integer :: &
|
||||||
|
maxNinstance ! no pInt (stores a system dependen value from 'count'
|
||||||
|
|
||||||
|
write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_NONE_label//' init -+>>>'
|
||||||
|
write(6,'(a)') ' $Id$'
|
||||||
|
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||||
|
#include "compilation_info.f90"
|
||||||
|
|
||||||
|
maxNinstance = count(homogenization_type == HOMOGENIZATION_NONE_ID)
|
||||||
|
if (maxNinstance == 0) return
|
||||||
|
|
||||||
|
end subroutine homogenization_none_init
|
||||||
|
|
||||||
|
end module homogenization_none
|
|
@ -42,6 +42,7 @@ module material
|
||||||
PLASTICITY_DISLOTWIN_label = 'dislotwin', &
|
PLASTICITY_DISLOTWIN_label = 'dislotwin', &
|
||||||
PLASTICITY_TITANMOD_label = 'titanmod', &
|
PLASTICITY_TITANMOD_label = 'titanmod', &
|
||||||
PLASTICITY_NONLOCAL_label = 'nonlocal', &
|
PLASTICITY_NONLOCAL_label = 'nonlocal', &
|
||||||
|
HOMOGENIZATION_NONE_label = 'none', &
|
||||||
HOMOGENIZATION_ISOSTRAIN_label = 'isostrain', &
|
HOMOGENIZATION_ISOSTRAIN_label = 'isostrain', &
|
||||||
HOMOGENIZATION_RGC_label = 'rgc'
|
HOMOGENIZATION_RGC_label = 'rgc'
|
||||||
|
|
||||||
|
@ -60,6 +61,7 @@ module material
|
||||||
end enum
|
end enum
|
||||||
enum, bind(c)
|
enum, bind(c)
|
||||||
enumerator :: HOMOGENIZATION_undefined_ID, &
|
enumerator :: HOMOGENIZATION_undefined_ID, &
|
||||||
|
HOMOGENIZATION_none_ID, &
|
||||||
HOMOGENIZATION_isostrain_ID, &
|
HOMOGENIZATION_isostrain_ID, &
|
||||||
HOMOGENIZATION_RGC_ID
|
HOMOGENIZATION_RGC_ID
|
||||||
end enum
|
end enum
|
||||||
|
@ -165,6 +167,7 @@ module material
|
||||||
PLASTICITY_dislotwin_ID, &
|
PLASTICITY_dislotwin_ID, &
|
||||||
PLASTICITY_titanmod_ID, &
|
PLASTICITY_titanmod_ID, &
|
||||||
PLASTICITY_nonlocal_ID, &
|
PLASTICITY_nonlocal_ID, &
|
||||||
|
HOMOGENIZATION_none_ID, &
|
||||||
HOMOGENIZATION_isostrain_ID, &
|
HOMOGENIZATION_isostrain_ID, &
|
||||||
HOMOGENIZATION_RGC_ID
|
HOMOGENIZATION_RGC_ID
|
||||||
|
|
||||||
|
@ -341,6 +344,9 @@ subroutine material_parseHomogenization(fileUnit,myPart)
|
||||||
select case(tag)
|
select case(tag)
|
||||||
case ('type')
|
case ('type')
|
||||||
select case (IO_lc(IO_stringValue(line,positions,2_pInt)))
|
select case (IO_lc(IO_stringValue(line,positions,2_pInt)))
|
||||||
|
case(HOMOGENIZATION_NONE_label)
|
||||||
|
homogenization_type(section) = HOMOGENIZATION_NONE_ID
|
||||||
|
homogenization_Ngrains(section) = 1_pInt
|
||||||
case(HOMOGENIZATION_ISOSTRAIN_label)
|
case(HOMOGENIZATION_ISOSTRAIN_label)
|
||||||
homogenization_type(section) = HOMOGENIZATION_ISOSTRAIN_ID
|
homogenization_type(section) = HOMOGENIZATION_ISOSTRAIN_ID
|
||||||
case(HOMOGENIZATION_RGC_label)
|
case(HOMOGENIZATION_RGC_label)
|
||||||
|
|
Loading…
Reference in New Issue