Skip to content

Commit

Permalink
adds individual pattern tiff output to EMECP program
Browse files Browse the repository at this point in the history
  • Loading branch information
marcdegraef committed Jan 23, 2024
1 parent 4ba0cf9 commit 521eb17
Show file tree
Hide file tree
Showing 5 changed files with 53 additions and 8 deletions.
3 changes: 3 additions & 0 deletions NamelistTemplates/EMECP.template
Expand Up @@ -25,6 +25,9 @@
outputformat = 'gui',
! output file ; path relative to EMdatapathname
datafile = 'undefined',
! file prefix to save individual patterns as tiff files (relative to EMdatapathname)
! [probably best to save them in a separate folder, so they can be loaded as an image stack in Fiji]
tiff_prefix = 'undefined',
! number of threads for parallel execution
nthreads = 1,
! tilt of the sample; only one angle incorporated for now
Expand Down
5 changes: 5 additions & 0 deletions Source/EMsoftHDFLib/NameListHDFwriters.f90
Expand Up @@ -3388,6 +3388,11 @@ recursive subroutine HDFwriteECPNameList(HDF_head, ecpnl, twolayerflag)
hdferr = HDF_writeDatasetStringArray(dataset, line2, 1, HDF_head)
if (hdferr.ne.0) call HDF_handleError(hdferr,'HDFwriteECPNameList: unable to create datafile dataset',.TRUE.)

dataset = 'tiff_prefix'
line2(1) = ecpnl%tiff_prefix
hdferr = HDF_writeDatasetStringArray(dataset, line2, 1, HDF_head)
if (hdferr.ne.0) call HDF_handleError(hdferr,'HDFwriteECPNameList: unable to create tiff_prefix dataset',.TRUE.)

dataset = SC_xtalname
line2(1) = ecpnl%xtalname
hdferr = HDF_writeDatasetStringArray(dataset, line2, 1, HDF_head)
Expand Down
5 changes: 4 additions & 1 deletion Source/EMsoftLib/NameListHandlers.f90
Expand Up @@ -5797,6 +5797,7 @@ recursive subroutine GetECPNameList(nmlfile, ecpnl, initonly)
character(fnlen) :: datafile
character(1) :: maskpattern
character(fnlen) :: anglefile
character(fnlen) :: tiff_prefix
character(3) :: eulerconvention
integer(kind=irg) :: numangle_anglefile
real(kind=sgl) :: gammavalue
Expand All @@ -5808,7 +5809,7 @@ recursive subroutine GetECPNameList(nmlfile, ecpnl, initonly)

! namelist /ECPlist/ stdout, xtalname, voltage, k, fn, dmin, distort, abcdist, albegadist, ktmax, &
namelist /ECPlist/ stdout, xtalname, xtalname2, fn_f, fn_s, dmin, filmthickness, anglefile, &
nthreads, thetac, npix, maskpattern, eulerconvention, Rin, Rout, &
nthreads, thetac, npix, maskpattern, eulerconvention, Rin, Rout, tiff_prefix, &
gF, gS, tF, tS, energyfile, filmfile, subsfile, masterfile, datafile, &
numangle_anglefile, gammavalue, outputformat, sampletilt, workingdistance

Expand All @@ -5832,6 +5833,7 @@ recursive subroutine GetECPNameList(nmlfile, ecpnl, initonly)
subsfile = 'undefined'
masterfile = 'undefined'
datafile = 'undefined'
tiff_prefix = 'undefined'
maskpattern = 'y'
anglefile = 'undefined'
eulerconvention = 'hkl'
Expand Down Expand Up @@ -5880,6 +5882,7 @@ recursive subroutine GetECPNameList(nmlfile, ecpnl, initonly)
ecpnl%masterfile = masterfile
ecpnl%maskpattern = maskpattern
ecpnl%anglefile = anglefile
ecpnl%tiff_prefix = tiff_prefix
ecpnl%numangle_anglefile = numangle_anglefile
ecpnl%eulerconvention = eulerconvention
ecpnl%gammavalue = gammavalue
Expand Down
1 change: 1 addition & 0 deletions Source/EMsoftLib/NameListTypedefs.f90
Expand Up @@ -1061,6 +1061,7 @@ module NameListTypedefs
character(fnlen) :: masterfile
character(fnlen) :: datafile
character(fnlen) :: anglefile
character(fnlen) :: tiff_prefix
character(3) :: eulerconvention
real(kind=sgl) :: gammavalue
character(3) :: outputformat
Expand Down
47 changes: 40 additions & 7 deletions Source/SEM/EMECP.f90
Expand Up @@ -113,6 +113,8 @@ subroutine ECpattern(ecpnl, progname, nmldeffile)
use distortion
use filters
use stringconstants
use image
use, intrinsic :: iso_fortran_env

IMPLICIT NONE

Expand Down Expand Up @@ -148,20 +150,29 @@ subroutine ECpattern(ecpnl, progname, nmldeffile)
real(kind=dbl) :: dp, MCangle
real(kind=dbl),parameter :: Rtod = 57.2957795131D0
real(kind=dbl),parameter :: dtoR = 0.01745329251D0
logical :: switchwfoff = .FALSE.
logical :: switchwfoff = .FALSE., tiff_output = .FALSE.
!complex(kind=dbl) :: D

type(HDFobjectStackType) :: HDF_head
integer(HSIZE_T), dimension(1:3) :: hdims, offset
integer(HSIZE_T) :: dims3(3)
character(fnlen,kind=c_char) :: line2(1)
character(fnlen) :: groupname, dataset, attributename, HDF_FileVersion
character(fnlen) :: groupname, dataset, attributename, HDF_FileVersion, TIFF_filename
character(11) :: dstr
character(15) :: tstrb
character(15) :: tstre
character(fnlen) :: datafile
logical :: overwrite = .TRUE., insert = .TRUE.

! declare variables for use in object oriented image module
integer :: iostat
character(len=128) :: iomsg
logical :: isInteger
type(image_t) :: im
character(5) :: TIFF_number
integer(int8) :: i8 (3,4)
integer(int8), allocatable :: TIFF_image(:,:)

!=================================================================
! read Monte Carlo output file and extract necessary parameters
! first, we need to load the data from the output of EMMCOpenCL
Expand Down Expand Up @@ -220,11 +231,12 @@ subroutine ECpattern(ecpnl, progname, nmldeffile)
switchwfoff = .TRUE.
end if


!=================================================================
! completed reading the file; generating list of incident vectors
!=================================================================

if (trim(ecpnl%tiff_prefix).ne.'undefined') tiff_output = .TRUE.

numk = 0
call GetVectorsCone(ecpnl, khead, numk)
allocate(kij(2,numk),klist(3,numk),stat=istat)
Expand Down Expand Up @@ -376,12 +388,14 @@ subroutine ECpattern(ecpnl, progname, nmldeffile)

! use OpenMP to run on multiple cores
!$OMP PARALLEL DEFAULT(SHARED) &
!$OMP PRIVATE(TID,nthreads,dc,ixy,istat,nix,niy,nixp,niyp,dx,dy,dxm,dym,MCangle,isig,dp,isigp) &
!$OMP PRIVATE(TID,nthreads,dc,ixy,istat,nix,niy,nixp,niyp,dx,dy,dxm,dym,MCangle,isig,dp,isigp,TIFF_image) &
!$OMP& PRIVATE(ipx,ipy,ECPpattern,bpat,ECPpatternintd,ma,mi,offset,hdims,dims3,hdferr,qu,idir,wf)

TID = OMP_GET_THREAD_NUM()
nthreads = OMP_GET_NUM_THREADS()

if (tiff_output.eqv..TRUE.) allocate(TIFF_image(ecpnl%npix,ecpnl%npix))

!$OMP DO SCHEDULE(DYNAMIC)
angleloop: do iang = 1,ecpnl%numangle_anglefile
qu(1:4) = angles%quatang(1:4,iang)
Expand Down Expand Up @@ -493,11 +507,30 @@ subroutine ECpattern(ecpnl, progname, nmldeffile)
hdims = (/ ecpnl%npix, ecpnl%npix, ecpnl%numangle_anglefile /)
dims3 = (/ ecpnl%npix, ecpnl%npix, 1 /)
hdferr = HDF_writeHyperslabFloatArray3D(dataset, ECPpattern, hdims, offset, dims3, HDF_head, insert)
! =====================================================
! end of HDF_FileVersion = 4.0 write statements
! =====================================================
end if

if (tiff_output.eqv..TRUE.) then
! Create a tiff file name
TIFF_filename = trim(EMsoft_getEMdatapathname())//trim(ecpnl%tiff_prefix)
write (tiff_number,"(I5.5)") iang-1
TIFF_filename = trim(TIFF_filename)//tiff_number//'.tiff'
TIFF_filename = EMsoft_toNativePath(TIFF_filename)
ma = maxval(ECPpattern)
mi = minval(ECPpattern)
ECPpatternintd = ((ECPpattern - mi)/ (ma-mi))
if (ecpnl%maskpattern.eq.'y') ECPpatternintd = ECPpatternintd * mask
TIFF_image = nint(255.0*ECPpatternintd)
! set up the image_t structure
im = image_t(TIFF_image)
if(im%empty()) call Message("EMECP","failed to convert array to image")

! create the file
call im%write(trim(TIFF_filename), iostat, iomsg) ! format automatically detected from extension
if(0.ne.iostat) then
call Message("failed to write image to file : "//iomsg)
end if
end if

!$OMP END CRITICAL

end do angleloop
Expand Down

0 comments on commit 521eb17

Please sign in to comment.