Added print messages to let user know whats going on

This commit is contained in:
Alex Selimov 2020-01-28 10:42:30 -05:00
parent e91bcd5d1e
commit 9ebdfff0a1
6 changed files with 62 additions and 15 deletions

View file

@ -23,12 +23,12 @@ module opt_disl
contains
subroutine dislocation(option, arg_pos)
!Main calling function for all codes related to dislocations
character(len=100), intent(in) :: option
integer, intent(inout) :: arg_pos
print *, '--------------------Option Dislocation-----------------------'
select case(trim(adjustl(option)))
case('-dislgen')
@ -97,6 +97,8 @@ module opt_disl
real(kind=dp) :: ss_ori(3,3), ss_inv(3,3), be, bs, slipx(3), disp_transform(3,3), inv_transform(3,3), &
actan, r(3), disp(3)
print *, "Dislocation with centroid ", centroid, " is inserted"
!Calculate screw and edge burgers vectors
be = sin(char_angle*pi/180.0_dp)*b
bs = cos(char_angle*pi/180.0_dp)*b
@ -254,6 +256,9 @@ module opt_disl
real(kind = dp) :: perimeter, angle, theta, omega, xA(3), xB(3), xC(3), u(3)
real(kind=dp), dimension(:,:), allocatable :: xloop !coordinate of points forming loop
print *, "Dislocation loop with centroid ", centroid, " is inserted"
if(allocated(xLoop)) deallocate(xLoop)
!Define new directions