!prec.f90 407 2009-08-31 15:09:15Z MPIE\f.roters !############################################################## MODULE prec !############################################################## implicit none ! *** Precision of real and integer variables *** integer, parameter :: pReal = selected_real_kind(15,300) ! 15 significant digits, up to 1e+-300 integer, parameter :: pInt = selected_int_kind(9) ! up to +- 1e9 integer, parameter :: pLongInt = 8 ! should be 64bit END MODULE prec !IO.f90 693 2010-11-04 18:18:01Z MPIE\c.kords !############################################################## MODULE IO !############################################################## CONTAINS !******************************************************************** ! identifies lines without content !******************************************************************** pure function IO_isBlank (line) use prec, only: pInt implicit none character(len=*), intent(in) :: line character(len=*), parameter :: blank = achar(32)//achar(9)//achar(10)//achar(13) ! whitespaces character(len=*), parameter :: comment = achar(35) ! comment id '#' integer(pInt) posNonBlank, posComment logical IO_isBlank posNonBlank = verify(line,blank) posComment = scan(line,comment) IO_isBlank = posNonBlank == 0 .or. posNonBlank == posComment return endfunction !******************************************************************** ! read string value at pos from line !******************************************************************** pure function IO_stringValue (line,positions,pos) use prec, only: pReal,pInt implicit none character(len=*), intent(in) :: line integer(pInt), intent(in) :: positions(*),pos character(len=1+positions(pos*2+1)-positions(pos*2)) IO_stringValue if (positions(1) < pos) then IO_stringValue = '' else IO_stringValue = line(positions(pos*2):positions(pos*2+1)) endif return endfunction !******************************************************************** ! read float value at pos from line !******************************************************************** pure function IO_floatValue (line,positions,pos) use prec, only: pReal,pInt implicit none character(len=*), intent(in) :: line integer(pInt), intent(in) :: positions(*),pos real(pReal) IO_floatValue if (positions(1) < pos) then IO_floatValue = 0.0_pReal else read(UNIT=line(positions(pos*2):positions(pos*2+1)),ERR=100,FMT=*) IO_floatValue endif return 100 IO_floatValue = huge(1.0_pReal) return endfunction !******************************************************************** ! read int value at pos from line !******************************************************************** pure function IO_intValue (line,positions,pos) use prec, only: pReal,pInt implicit none character(len=*), intent(in) :: line integer(pInt), intent(in) :: positions(*),pos integer(pInt) IO_intValue if (positions(1) < pos) then IO_intValue = 0_pInt else read(UNIT=line(positions(pos*2):positions(pos*2+1)),ERR=100,FMT=*) IO_intValue endif return 100 IO_intValue = huge(1_pInt) return endfunction !******************************************************************** ! change character in line to lower case !******************************************************************** pure function IO_lc (line) use prec, only: pInt implicit none character (len=*), intent(in) :: line character (len=len(line)) IO_lc integer(pInt) i IO_lc = line do i=1,len(line) if(640) left = right + verify(line(right+1:),sep) right = left + scan(line(left:),sep) - 2 if ( IO_stringPos(1)' format1 = '(A, I'//trim(N_Digits)//'.'//trim(N_Digits)//', A)' format2 = '(A, I'//trim(N_Digits)//', A)' do i = 1, N_Seeds write(20, trim(format1)), '[Grain', i, ']' write(20, '(A)'), 'crystallite 1' write(20, trim(format2)), '(constituent) phase 1 texture ', i, ' fraction 1.0' end do ! get random euler angles for every grain, store them in grainEuler and write them to the material.config file format2 = '(6(A, F10.6))' write(20, '(/, A)'), '' do i = 1, N_Seeds write(20, trim(format1)), '[Grain', i, ']' write(20, trim(format2)), '(gauss) phi1 ', grainEuler(i,1), ' Phi ', grainEuler(i,2), & &' Phi2 ', grainEuler(i,3), ' scatter 0.0 fraction 1.0' end do close(20) print*, 'material.config done.' !write header of geom file open(20, file = ((trim(output_name))//'.geom')) open(21, file = ((trim(output_name))//'.spectral')) write(20, '(A)'), '3 header' write(20, '(A, I8, A, I8, A, I8)'), 'resolution a ', resolution(1), ' b ', resolution(2), ' c ', resolution(3) write(20, '(A, g17.10, A, g17.10, A, g17.10)'), 'dimension x ', geomdim(1), ' y ', geomdim(2), ' z ', geomdim(3) write(20, '(A)'), 'homogenization 1' format1 = '(I'//trim(N_Digits)//'.'//trim(N_Digits)//')' ! geom format format2 = '(3(tr2, f6.2), 3(tr2,g10.5), I10, a)' ! spectral (Lebensohn) format ! perform voronoi tessellation and write result to files do i = 0, resolution(1)*resolution(2)*resolution(3)-1 minDist = geomdim(1)*geomdim(1)+geomdim(2)*geomdim(2)+geomdim(3)*geomdim(3) ! diagonal of rve do j = 1, N_Seeds delta(1) = step(1)*(mod(i , resolution(1))+0.5_pReal) - seeds(j,1) delta(2) = step(2)*(mod(i/resolution(1) , resolution(2))+0.5_pReal) - seeds(j,2) delta(3) = step(3)*(mod(i/resolution(1)/resolution(2), resolution(3))+0.5_pReal) - seeds(j,3) do k = -1, 1 ! left, me, right image do l = -1, 1 ! front, me, back image do m = -1, 1 ! lower, me, upper image theDist = ( geomdim(1) * ( delta(1)-real(k,pReal) ) )**2 + & ( geomdim(2) * ( delta(2)-real(l,pReal) ) )**2 + & ( geomdim(3) * ( delta(3)-real(m,pReal) ) )**2 if (theDist < minDist) then minDist = theDist theGrain = j endif enddo enddo enddo enddo grainCheck(theGrain) = .true. write(20, trim(format1)), theGrain write(21, trim(format2)), grainEuler(theGrain,1), grainEuler(theGrain,2), grainEuler(theGrain,3), & geomdim(1)*step(1)*(mod(i , resolution(1))+0.5_pReal), & geomdim(2)*step(2)*(mod(i/resolution(1) , resolution(2))+0.5_pReal), & geomdim(3)*step(3)*(mod(i/resolution(1)/resolution(2), resolution(3))+0.5_pReal), & theGrain, ' 1' enddo close(20) close(21) print*, 'voronoi tesselation done.' if (all(grainCheck)) then print*, 'all grains mapped!' else print*, 'only',count(grainCheck),'grains mapped!' endif end program voronoi