Skip to content

Commit

Permalink
modification of DI nml reading (temporary simplification)
Browse files Browse the repository at this point in the history
  • Loading branch information
marcdegraef committed Dec 12, 2024
1 parent 1710e47 commit c88e315
Show file tree
Hide file tree
Showing 2 changed files with 43 additions and 23 deletions.
3 changes: 3 additions & 0 deletions NamelistTemplates/EMHREBSDDIC.template
Original file line number Diff line number Diff line change
Expand Up @@ -3,11 +3,14 @@
! EBSD Pattern Parameters will be read from an EMDI output file
!###################################################################
! name of the dot product file (.h5) path relative to EMdatapathname
! not needed in the first version of this program...
DIfile = 'undefined',
! output HDF5 file; path relative to EMdatapathname
datafile = 'undefined',
! relative path to the namelist file for EMppEBSD program
ppEBSDnml = 'undefined'
! relative path to the namelist file for EMDI program
DInml = 'undefined'
! coordinates of the reference pattern to be used (0-based coordinates)
patx = 0,
paty = 0,
Expand Down
63 changes: 40 additions & 23 deletions Source/EMsoftOOLib/program_mods/mod_HREBSDDIC.f90
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,7 @@ module mod_HREBSDDIC
use mod_kinds
use mod_global
use mod_ppEBSD, only : ppEBSDNameListType
use mod_DIfiles, only : DictionaryIndexingNameListType

IMPLICIT NONE

Expand All @@ -56,6 +57,7 @@ module mod_HREBSDDIC
character(fnlen) :: DIfile
character(fnlen) :: datafile
character(fnlen) :: ppEBSDnml
character(fnlen) :: DInml
character(3) :: crystal
end type HREBSDDICNameListType

Expand All @@ -65,6 +67,7 @@ module mod_HREBSDDIC
character(fnlen) :: nmldeffile = 'EMHREBSDDIC.nml'
type(HREBSDDICNameListType) :: nml
type(ppEBSDNameListType) :: ppEBSDnml
type(DictionaryIndexingNameListType) :: DInml

contains
private
Expand Down Expand Up @@ -97,20 +100,26 @@ type(HREBSD_DIC_T) function HREBSDDIC_constructor( nmlfile ) result(HREBSDDIC)
!! constructor for the HREBSD_DIC_T Class;

use mod_ppEBSD, only : ppEBSD_T
use mod_DIfiles, only : DIfile_T

IMPLICIT NONE

character(fnlen), INTENT(IN) :: nmlfile
type(ppEBSD_T) :: ppEBSD
type(DIfile_T) :: DIFT

call HREBSDDIC%readNameList(nmlfile)

! we also need to read in the namelist file from the EMppEBSD program
! we also need to read in the namelist fileis from the EMppEBSD and EMDI programs (for now)
! this file defines where the original patterns are located as well
! as information about their size etc.
ppEBSD = ppEBSD_T( HREBSDDIC%nml%ppEBSDnml )
HREBSDDIC%ppEBSDnml = ppEBSD%get_nml()

DIFT = DIfile_T()
call DIFT%readNameList(HREBSDDIC%nml%DInml)
HREBSDDIC%DInml = DIFT%getNameList()

end function HREBSDDIC_constructor

!--------------------------------------------------------------------------
Expand Down Expand Up @@ -168,9 +177,10 @@ subroutine readNameList_(self, nmlfile, initonly)
character(fnlen) :: DIfile
character(fnlen) :: datafile
character(fnlen) :: ppEBSDnml
character(fnlen) :: DInml
character(3) :: crystal

namelist / HREBSDDICdata / patx, paty, nthreads, C11, C12, C44, C13, C33, DIfile, &
namelist / HREBSDDICdata / patx, paty, nthreads, C11, C12, C44, C13, C33, DIfile, DInml, &
datafile, patternfile, DIfile, ppEBSDnml, crystal, nbx, nby

patx = 0
Expand All @@ -187,6 +197,7 @@ subroutine readNameList_(self, nmlfile, initonly)
datafile = 'undefined'
DIfile = 'undefined'
ppEBSDnml = 'undefined'
DInml = 'undefined'
crystal = 'cub'

if (present(initonly)) then
Expand All @@ -204,14 +215,18 @@ subroutine readNameList_(self, nmlfile, initonly)
call Message%printError('readNameList:',' patternfile name is undefined in '//nmlfile)
end if

if (trim(DIfile).eq.'undefined') then
call Message%printError('readNameList:',' DIfile file name is undefined in '//nmlfile)
end if
! if (trim(DIfile).eq.'undefined') then
! call Message%printError('readNameList:',' DIfile file name is undefined in '//nmlfile)
! end if

if (trim(ppEBSDnml).eq.'undefined') then
call Message%printError('readNameList:',' ppEBSDnml file name is undefined in '//nmlfile)
end if

if (trim(DInml).eq.'undefined') then
call Message%printError('readNameList:',' DInml file name is undefined in '//nmlfile)
end if

if (trim(datafile).eq.'undefined') then
call Message%printError('readNameList:',' datafile file name is undefined in '//nmlfile)
end if
Expand All @@ -232,6 +247,7 @@ subroutine readNameList_(self, nmlfile, initonly)
self%nml%DIfile = DIfile
self%nml%datafile = datafile
self%nml%ppEBSDnml = ppEBSDnml
self%nml%DInml = DInml
self%nml%crystal = crystal

end subroutine readNameList_
Expand Down Expand Up @@ -326,6 +342,11 @@ recursive subroutine writeHDFNameList_(self, HDF, HDFnames)
hdferr = HDF%writeDatasetStringArray(dataset, line2, 1)
if (hdferr.ne.0) call HDF%error_check('writeHDFNameList: unable to create ppEBSDnml dataset', hdferr)

dataset = 'DInml'
line2(1) = trim(enl%DInml)
hdferr = HDF%writeDatasetStringArray(dataset, line2, 1)
if (hdferr.ne.0) call HDF%error_check('writeHDFNameList: unable to create DInml dataset', hdferr)

dataset = 'crystal'
line2(1) = trim(enl%crystal)
hdferr = HDF%writeDatasetStringArray(dataset, line2, 1)
Expand Down Expand Up @@ -420,30 +441,29 @@ subroutine HREBSD_DIC_(self, EMsoft, progname, HDFnames)
! this program reads a dot product EMDI file, including all the experimental parameters
! as well as a pre-processed pattern file generated by EMppEBSD.

associate( enl => self%nml, dinl=>DIFT%nml )
associate( enl => self%nml, dinl=>self%DInml )

call setRotationPrecision('d')
call openFortranHDFInterface()

! if (1.eq.0) then
! read all parameters from the EMDI output file
DIfile = EMsoft%generateFilePath('EMdatapathname',trim(enl%DIfile))
! for now, we only read the EMDI.nml file, so we do not really need the full dot product file
! in a later version we will likely need the complete file
! DIfile = EMsoft%generateFilePath('EMdatapathname',trim(enl%DIfile))

HDFnames2 = HDFnames_T()
call HDFnames2%set_NMLfiles(SC_NMLfiles)
call HDFnames2%set_NMLfilename(SC_DictionaryIndexingNML)
call HDFnames2%set_NMLparameters(SC_NMLparameters)
call HDFnames2%set_NMLlist(SC_DictionaryIndexingNameListType)
! HDFnames2 = HDFnames_T()
! call HDFnames2%set_NMLfiles(SC_NMLfiles)
! call HDFnames2%set_NMLfilename(SC_DictionaryIndexingNML)
! call HDFnames2%set_NMLparameters(SC_NMLparameters)
! call HDFnames2%set_NMLlist(SC_DictionaryIndexingNameListType)

call DIFT%readDotProductFile(EMsoft, HDF, HDFnames2, DIfile, hdferr, &
getPhi1=.TRUE., &
getPhi=.TRUE., &
getPhi2=.TRUE.)
! call DIFT%readDotProductFile(EMsoft, HDF, HDFnames2, DIfile, hdferr, &
! getPhi1=.TRUE., &
! getPhi=.TRUE., &
! getPhi2=.TRUE.)

fpar = (/ real(dinl%exptnumsx), real(dinl%exptnumsy), real(dinl%delta) /)

! end if

! use the memory class for most array allocations
mem = Memory_T()

Expand Down Expand Up @@ -717,15 +737,12 @@ subroutine HREBSD_DIC_(self, EMsoft, progname, HDFnames)
hdferr = HDF%writeDatasetIntegerArray(dataset, nit, numpats)
end if

!call HDF%pop()
!call HDF%popall()
call HDF%popall()

call closeFortranHDFInterface()

end associate

! call mem%allocated_memory_use(' after dealloc')

end subroutine HREBSD_DIC_


Expand Down

0 comments on commit c88e315

Please sign in to comment.