2018-12-08 12:32:55 +05:30
|
|
|
! ###################################################################
|
|
|
|
! Copyright (c) 2013-2014, Marc De Graef/Carnegie Mellon University
|
2019-02-01 14:31:54 +05:30
|
|
|
! Modified 2017-2019, Martin Diehl/Max-Planck-Institut für Eisenforschung GmbH
|
2018-12-08 12:32:55 +05:30
|
|
|
! All rights reserved.
|
|
|
|
!
|
|
|
|
! Redistribution and use in source and binary forms, with or without modification, are
|
|
|
|
! permitted provided that the following conditions are met:
|
|
|
|
!
|
|
|
|
! - Redistributions of source code must retain the above copyright notice, this list
|
|
|
|
! of conditions and the following disclaimer.
|
|
|
|
! - Redistributions in binary form must reproduce the above copyright notice, this
|
|
|
|
! list of conditions and the following disclaimer in the documentation and/or
|
|
|
|
! other materials provided with the distribution.
|
|
|
|
! - Neither the names of Marc De Graef, Carnegie Mellon University nor the names
|
|
|
|
! of its contributors may be used to endorse or promote products derived from
|
|
|
|
! this software without specific prior written permission.
|
|
|
|
!
|
|
|
|
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
|
|
|
|
! AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
|
|
|
|
! IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
|
|
|
|
! ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE
|
|
|
|
! LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
|
|
|
|
! DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
|
|
|
|
! SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
|
|
|
|
! CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY,
|
|
|
|
! OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE
|
|
|
|
! USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
|
|
|
|
! ###################################################################
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
|
|
|
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @brief rotation storage and conversion
|
|
|
|
!> @details: rotation is internally stored as quaternion. It cabe inialized from different
|
|
|
|
!> represantations and also returns itself in different representations.
|
2019-02-01 14:47:20 +05:30
|
|
|
!
|
|
|
|
! All methods and naming conventions based on Rowenhorst_etal2015
|
|
|
|
! Convention 1: coordinate frames are right-handed
|
|
|
|
! Convention 2: a rotation angle ω is taken to be positive for a counterclockwise rotation
|
|
|
|
! when viewing from the end point of the rotation axis towards the origin
|
|
|
|
! Convention 3: rotations will be interpreted in the passive sense
|
|
|
|
! Convention 4: Euler angle triplets are implemented using the Bunge convention,
|
|
|
|
! with the angular ranges as [0, 2π],[0, π],[0, 2π]
|
|
|
|
! Convention 5: the rotation angle ω is limited to the interval [0, π]
|
2019-02-01 23:39:17 +05:30
|
|
|
! Convention 6: P = -1
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
|
2018-12-08 12:32:55 +05:30
|
|
|
module rotations
|
2019-05-17 02:26:48 +05:30
|
|
|
use prec
|
|
|
|
use IO
|
|
|
|
use math
|
|
|
|
use Lambert
|
2019-04-03 16:41:18 +05:30
|
|
|
use quaternions
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
private
|
2019-05-17 02:26:48 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
type, public :: rotation
|
|
|
|
type(quaternion), private :: q
|
|
|
|
contains
|
|
|
|
procedure, public :: asQuaternion
|
|
|
|
procedure, public :: asEulerAngles
|
|
|
|
procedure, public :: asAxisAnglePair
|
|
|
|
procedure, public :: asRodriguesFrankVector
|
|
|
|
procedure, public :: asRotationMatrix
|
|
|
|
!------------------------------------------
|
2019-06-07 18:00:16 +05:30
|
|
|
procedure, public :: fromEulerAngles
|
2019-09-20 11:20:30 +05:30
|
|
|
procedure, public :: fromAxisAnglePair
|
|
|
|
procedure, public :: fromRotationMatrix
|
2019-04-03 16:41:18 +05:30
|
|
|
!------------------------------------------
|
2019-09-20 11:20:30 +05:30
|
|
|
procedure, private :: rotRot__
|
|
|
|
generic, public :: operator(*) => rotRot__
|
|
|
|
procedure, public :: rotVector
|
|
|
|
procedure, public :: rotTensor
|
|
|
|
procedure, public :: misorientation
|
2019-04-03 16:41:18 +05:30
|
|
|
end type rotation
|
2019-02-02 00:47:12 +05:30
|
|
|
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
contains
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
! Return rotation in different represenations
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-02-02 00:47:12 +05:30
|
|
|
function asQuaternion(self)
|
2019-02-01 14:31:54 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
class(rotation), intent(in) :: self
|
|
|
|
real(pReal), dimension(4) :: asQuaternion
|
|
|
|
|
|
|
|
asQuaternion = [self%q%w, self%q%x, self%q%y, self%q%z]
|
2018-12-08 17:33:27 +05:30
|
|
|
|
|
|
|
end function asQuaternion
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-02-02 00:47:12 +05:30
|
|
|
function asEulerAngles(self)
|
2019-02-01 14:31:54 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
class(rotation), intent(in) :: self
|
|
|
|
real(pReal), dimension(3) :: asEulerAngles
|
|
|
|
|
|
|
|
asEulerAngles = qu2eu(self%q)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
end function asEulerAngles
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-02-02 00:47:12 +05:30
|
|
|
function asAxisAnglePair(self)
|
2019-02-01 14:31:54 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
class(rotation), intent(in) :: self
|
|
|
|
real(pReal), dimension(4) :: asAxisAnglePair
|
|
|
|
|
|
|
|
asAxisAnglePair = qu2ax(self%q)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
end function asAxisAnglePair
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-02-02 00:47:12 +05:30
|
|
|
function asRotationMatrix(self)
|
2019-02-01 14:31:54 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
class(rotation), intent(in) :: self
|
|
|
|
real(pReal), dimension(3,3) :: asRotationMatrix
|
|
|
|
|
|
|
|
asRotationMatrix = qu2om(self%q)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
end function asRotationMatrix
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-02-02 00:47:12 +05:30
|
|
|
function asRodriguesFrankVector(self)
|
2019-02-01 14:31:54 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
class(rotation), intent(in) :: self
|
|
|
|
real(pReal), dimension(4) :: asRodriguesFrankVector
|
|
|
|
|
|
|
|
asRodriguesFrankVector = qu2ro(self%q)
|
2019-02-01 14:31:54 +05:30
|
|
|
|
2018-12-08 12:32:55 +05:30
|
|
|
end function asRodriguesFrankVector
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-02-02 00:47:12 +05:30
|
|
|
function asHomochoric(self)
|
2019-02-01 14:31:54 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
class(rotation), intent(in) :: self
|
|
|
|
real(pReal), dimension(3) :: asHomochoric
|
|
|
|
|
|
|
|
asHomochoric = qu2ho(self%q)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
end function asHomochoric
|
2019-02-01 14:31:54 +05:30
|
|
|
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
! Initialize rotation from different representations
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-09-20 07:44:37 +05:30
|
|
|
subroutine fromEulerAngles(self,eu,degrees)
|
2019-06-07 18:00:16 +05:30
|
|
|
|
|
|
|
class(rotation), intent(out) :: self
|
|
|
|
real(pReal), dimension(3), intent(in) :: eu
|
2019-09-20 07:44:37 +05:30
|
|
|
logical, intent(in), optional :: degrees
|
|
|
|
|
|
|
|
if (.not. present(degrees)) then
|
|
|
|
self%q = eu2qu(eu)
|
|
|
|
else
|
|
|
|
self%q = eu2qu(merge(eu*INRAD,eu,degrees))
|
|
|
|
endif
|
|
|
|
|
2019-09-20 11:20:30 +05:30
|
|
|
end subroutine fromEulerAngles
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
subroutine fromAxisAnglePair(self,ax,degrees)
|
|
|
|
|
|
|
|
class(rotation), intent(out) :: self
|
|
|
|
real(pReal), dimension(4), intent(in) :: ax
|
|
|
|
logical, intent(in), optional :: degrees
|
|
|
|
|
|
|
|
if (.not. present(degrees)) then
|
|
|
|
self%q = ax2qu(ax)
|
|
|
|
else
|
|
|
|
self%q = ax2qu(merge([ax(1:3),ax(4)*INRAD],ax,degrees))
|
|
|
|
endif
|
|
|
|
|
|
|
|
end subroutine fromAxisAnglePair
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
subroutine fromRotationMatrix(self,om)
|
|
|
|
|
|
|
|
class(rotation), intent(out) :: self
|
|
|
|
real(pReal), dimension(3,3), intent(in) :: om
|
|
|
|
|
|
|
|
self%q = om2qu(om)
|
2018-12-08 20:14:00 +05:30
|
|
|
|
2019-09-20 11:20:30 +05:30
|
|
|
end subroutine fromRotationMatrix
|
2019-06-07 18:00:16 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 20:14:00 +05:30
|
|
|
|
2019-09-20 11:20:30 +05:30
|
|
|
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief: Rotate a rotation
|
|
|
|
!> ToDo: completly untested
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
function rotRot__(self,r) result(rRot)
|
|
|
|
|
|
|
|
type(rotation) :: rRot
|
|
|
|
class(rotation), intent(in) :: self,r
|
|
|
|
|
|
|
|
rRot = rotation(self%q*r%q)
|
|
|
|
|
|
|
|
end function rotRot__
|
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-02-01 14:31:54 +05:30
|
|
|
!> @brief rotate a vector passively (default) or actively
|
|
|
|
!> @details: rotation is based on unit quaternion or rotation matrix (fallback)
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-09-20 11:20:30 +05:30
|
|
|
function rotVector(self,v,active) result(vRot)
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-09-20 11:20:30 +05:30
|
|
|
real(pReal), dimension(3) :: vRot
|
2019-04-03 16:41:18 +05:30
|
|
|
class(rotation), intent(in) :: self
|
|
|
|
real(pReal), intent(in), dimension(3) :: v
|
|
|
|
logical, intent(in), optional :: active
|
|
|
|
|
|
|
|
type(quaternion) :: q
|
|
|
|
logical :: passive
|
2019-02-01 14:31:54 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
if (present(active)) then
|
|
|
|
passive = .not. active
|
|
|
|
else
|
|
|
|
passive = .true.
|
|
|
|
endif
|
|
|
|
|
|
|
|
if (dEq(norm2(v),1.0_pReal,tol=1.0e-15_pReal)) then
|
|
|
|
if (passive) then
|
|
|
|
q = self%q * (quaternion([0.0_pReal, v(1), v(2), v(3)]) * conjg(self%q) )
|
|
|
|
else
|
|
|
|
q = conjg(self%q) * (quaternion([0.0_pReal, v(1), v(2), v(3)]) * self%q )
|
|
|
|
endif
|
2019-09-20 11:20:30 +05:30
|
|
|
vRot = [q%x,q%y,q%z]
|
2019-04-03 16:41:18 +05:30
|
|
|
else
|
|
|
|
if (passive) then
|
2019-09-20 11:20:30 +05:30
|
|
|
vRot = matmul(self%asRotationMatrix(),v)
|
2019-04-03 16:41:18 +05:30
|
|
|
else
|
2019-09-20 11:20:30 +05:30
|
|
|
vRot = matmul(transpose(self%asRotationMatrix()),v)
|
2019-04-03 16:41:18 +05:30
|
|
|
endif
|
|
|
|
endif
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
end function rotVector
|
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-02-01 14:31:54 +05:30
|
|
|
!> @brief rotate a second rank tensor passively (default) or actively
|
|
|
|
!> @details: rotation is based on rotation matrix
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-09-20 11:20:30 +05:30
|
|
|
function rotTensor(self,m,active) result(mRot)
|
2019-02-01 14:31:54 +05:30
|
|
|
|
2019-09-20 11:20:30 +05:30
|
|
|
real(pReal), dimension(3,3) :: mRot
|
2019-04-03 16:41:18 +05:30
|
|
|
class(rotation), intent(in) :: self
|
|
|
|
real(pReal), intent(in), dimension(3,3) :: m
|
|
|
|
logical, intent(in), optional :: active
|
|
|
|
|
|
|
|
logical :: passive
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
if (present(active)) then
|
|
|
|
passive = .not. active
|
|
|
|
else
|
|
|
|
passive = .true.
|
|
|
|
endif
|
|
|
|
|
|
|
|
if (passive) then
|
2019-09-20 11:20:30 +05:30
|
|
|
mRot = matmul(matmul(self%asRotationMatrix(),m),transpose(self%asRotationMatrix()))
|
2019-04-03 16:41:18 +05:30
|
|
|
else
|
2019-09-20 11:20:30 +05:30
|
|
|
mRot = matmul(matmul(transpose(self%asRotationMatrix()),m),self%asRotationMatrix())
|
2019-04-03 16:41:18 +05:30
|
|
|
endif
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
end function rotTensor
|
|
|
|
|
|
|
|
|
2019-02-02 00:47:12 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief misorientation
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
function misorientation(self,other)
|
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
type(rotation) :: misorientation
|
|
|
|
class(rotation), intent(in) :: self, other
|
|
|
|
|
|
|
|
misorientation%q = conjg(self%q) * other%q !ToDo: this is the convention used in math
|
2019-02-02 00:47:12 +05:30
|
|
|
|
|
|
|
end function misorientation
|
|
|
|
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
|
|
|
!> @brief convert unit quaternion to rotation matrix
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function qu2om(qu) result(om)
|
|
|
|
|
|
|
|
type(quaternion), intent(in) :: qu
|
|
|
|
real(pReal), dimension(3,3) :: om
|
|
|
|
|
|
|
|
real(pReal) :: qq
|
|
|
|
|
|
|
|
qq = qu%w**2-(qu%x**2 + qu%y**2 + qu%z**2)
|
|
|
|
|
|
|
|
|
|
|
|
om(1,1) = qq+2.0*qu%x*qu%x
|
|
|
|
om(2,2) = qq+2.0*qu%y*qu%y
|
|
|
|
om(3,3) = qq+2.0*qu%z*qu%z
|
|
|
|
|
|
|
|
om(1,2) = 2.0*(qu%x*qu%y-qu%w*qu%z)
|
|
|
|
om(2,3) = 2.0*(qu%y*qu%z-qu%w*qu%x)
|
|
|
|
om(3,1) = 2.0*(qu%z*qu%x-qu%w*qu%y)
|
|
|
|
om(2,1) = 2.0*(qu%y*qu%x+qu%w*qu%z)
|
|
|
|
om(3,2) = 2.0*(qu%z*qu%y+qu%w*qu%x)
|
|
|
|
om(1,3) = 2.0*(qu%x*qu%z+qu%w*qu%y)
|
|
|
|
|
|
|
|
if (P < 0.0) om = transpose(om)
|
|
|
|
|
|
|
|
end function qu2om
|
2019-02-01 14:31:54 +05:30
|
|
|
|
|
|
|
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert unit quaternion to Euler angles
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function qu2eu(qu) result(eu)
|
|
|
|
|
|
|
|
type(quaternion), intent(in) :: qu
|
|
|
|
real(pReal), dimension(3) :: eu
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal) :: q12, q03, chi, chiInv
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
q03 = qu%w**2+qu%z**2
|
|
|
|
q12 = qu%x**2+qu%y**2
|
|
|
|
chi = sqrt(q03*q12)
|
|
|
|
|
|
|
|
degenerated: if (dEq0(chi)) then
|
|
|
|
eu = merge([atan2(-P*2.0*qu%w*qu%z,qu%w**2-qu%z**2), 0.0_pReal, 0.0_pReal], &
|
|
|
|
[atan2(2.0*qu%x*qu%y,qu%x**2-qu%y**2), PI, 0.0_pReal], &
|
|
|
|
dEq0(q12))
|
|
|
|
else degenerated
|
|
|
|
chiInv = 1.0/chi
|
|
|
|
eu = [atan2((-P*qu%w*qu%y+qu%x*qu%z)*chi, (-P*qu%w*qu%x-qu%y*qu%z)*chi ), &
|
|
|
|
atan2( 2.0*chi, q03-q12 ), &
|
|
|
|
atan2(( P*qu%w*qu%y+qu%x*qu%z)*chi, (-P*qu%w*qu%x+qu%y*qu%z)*chi )]
|
|
|
|
endif degenerated
|
|
|
|
where(eu<0.0_pReal) eu = mod(eu+2.0_pReal*PI,[2.0_pReal*PI,PI,2.0_pReal*PI])
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function qu2eu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert unit quaternion to axis angle pair
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function qu2ax(qu) result(ax)
|
|
|
|
|
|
|
|
type(quaternion), intent(in) :: qu
|
|
|
|
real(pReal), dimension(4) :: ax
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal) :: omega, s
|
|
|
|
|
2019-04-17 16:21:00 +05:30
|
|
|
if (dEq0(qu%x**2+qu%y**2+qu%z**2)) then
|
|
|
|
ax = [ 0.0_pReal, 0.0_pReal, 1.0_pReal, 0.0_pReal ] ! axis = [001]
|
2019-04-17 01:47:56 +05:30
|
|
|
elseif (dNeq0(qu%w)) then
|
|
|
|
s = sign(1.0_pReal,qu%w)/sqrt(qu%x**2+qu%y**2+qu%z**2)
|
2019-04-17 16:21:00 +05:30
|
|
|
omega = 2.0_pReal * acos(math_clip(qu%w,-1.0_pReal,1.0_pReal))
|
2019-04-17 01:47:56 +05:30
|
|
|
ax = [ qu%x*s, qu%y*s, qu%z*s, omega ]
|
|
|
|
else
|
|
|
|
ax = [ qu%x, qu%y, qu%z, PI ]
|
|
|
|
end if
|
|
|
|
|
|
|
|
end function qu2ax
|
|
|
|
|
|
|
|
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
|
|
|
!> @brief convert unit quaternion to Rodrigues vector
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
pure function qu2ro(qu) result(ro)
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
type(quaternion), intent(in) :: qu
|
|
|
|
real(pReal), dimension(4) :: ro
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal) :: s
|
|
|
|
real(pReal), parameter :: thr = 1.0e-8_pReal
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
if (qu%w < thr) then
|
|
|
|
ro = [qu%x, qu%y, qu%z, IEEE_value(ro(4),IEEE_positive_inf)]
|
2019-04-03 16:41:18 +05:30
|
|
|
else
|
2019-04-17 01:47:56 +05:30
|
|
|
s = norm2([qu%x,qu%y,qu%z])
|
|
|
|
if (s < thr) then
|
|
|
|
ro = [ 0.0_pReal, 0.0_pReal, P, 0.0_pReal]
|
|
|
|
else
|
|
|
|
ro = [ qu%x/s, qu%y/s, qu%z/s, tan(acos(math_clip(qu%w,-1.0_pReal,1.0_pReal)))]
|
|
|
|
endif
|
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
end if
|
2019-04-17 01:47:56 +05:30
|
|
|
|
|
|
|
end function qu2ro
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert unit quaternion to homochoric
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function qu2ho(qu) result(ho)
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
type(quaternion), intent(in) :: qu
|
|
|
|
real(pReal), dimension(3) :: ho
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal) :: omega, f
|
|
|
|
|
|
|
|
omega = 2.0 * acos(math_clip(qu%w,-1.0_pReal,1.0_pReal))
|
|
|
|
|
|
|
|
if (dEq0(omega)) then
|
|
|
|
ho = [ 0.0, 0.0, 0.0 ]
|
2019-04-03 16:41:18 +05:30
|
|
|
else
|
2019-04-17 01:47:56 +05:30
|
|
|
ho = [qu%x, qu%y, qu%z]
|
|
|
|
f = 0.75 * ( omega - sin(omega) )
|
|
|
|
ho = ho/norm2(ho)* f**(1.0/3.0)
|
2019-04-03 16:41:18 +05:30
|
|
|
end if
|
2019-04-17 01:47:56 +05:30
|
|
|
|
|
|
|
end function qu2ho
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert unit quaternion to cubochoric
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
function qu2cu(qu) result(cu)
|
|
|
|
|
|
|
|
type(quaternion), intent(in) :: qu
|
|
|
|
real(pReal), dimension(3) :: cu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
cu = ho2cu(qu2ho(qu))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function qu2cu
|
|
|
|
|
|
|
|
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 16:21:00 +05:30
|
|
|
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @brief convert rotation matrix to cubochoric
|
|
|
|
!> @details the original formulation (direct conversion) had (numerical?) issues
|
2019-04-17 01:47:56 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-09-20 11:20:30 +05:30
|
|
|
pure function om2qu(om) result(qu)
|
2019-04-17 01:47:56 +05:30
|
|
|
|
2019-04-17 16:21:00 +05:30
|
|
|
real(pReal), intent(in), dimension(3,3) :: om
|
|
|
|
type(quaternion) :: qu
|
2019-04-17 01:47:56 +05:30
|
|
|
|
2019-04-17 16:21:00 +05:30
|
|
|
qu = eu2qu(om2eu(om))
|
2019-04-17 01:47:56 +05:30
|
|
|
|
|
|
|
end function om2qu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-02-01 14:31:54 +05:30
|
|
|
!> @brief orientation matrix to Euler angles
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
pure function om2eu(om) result(eu)
|
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
real(pReal), intent(in), dimension(3,3) :: om
|
|
|
|
real(pReal), dimension(3) :: eu
|
|
|
|
real(pReal) :: zeta
|
|
|
|
|
2019-04-17 18:49:41 +05:30
|
|
|
if (abs(om(3,3)) < 1.0_pReal) then
|
2019-04-03 16:41:18 +05:30
|
|
|
zeta = 1.0_pReal/sqrt(1.0_pReal-om(3,3)**2.0_pReal)
|
|
|
|
eu = [atan2(om(3,1)*zeta,-om(3,2)*zeta), &
|
|
|
|
acos(om(3,3)), &
|
|
|
|
atan2(om(1,3)*zeta, om(2,3)*zeta)]
|
2019-04-17 18:49:41 +05:30
|
|
|
else
|
|
|
|
eu = [ atan2( om(1,2),om(1,1)), 0.5*PI*(1-om(3,3)),0.0_pReal ]
|
2019-04-03 16:41:18 +05:30
|
|
|
end if
|
2019-04-17 18:49:41 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
where(eu<0.0_pReal) eu = mod(eu+2.0_pReal*PI,[2.0_pReal*PI,PI,2.0_pReal*PI])
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
end function om2eu
|
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert orientation matrix to axis angle pair
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
function om2ax(om) result(ax)
|
2019-04-03 16:41:18 +05:30
|
|
|
|
|
|
|
real(pReal), intent(in) :: om(3,3)
|
|
|
|
real(pReal) :: ax(4)
|
|
|
|
|
|
|
|
real(pReal) :: t
|
|
|
|
real(pReal), dimension(3) :: Wr, Wi
|
|
|
|
real(pReal), dimension(10) :: WORK
|
|
|
|
real(pReal), dimension(3,3) :: VR, devNull, o
|
|
|
|
integer :: INFO, LWORK, i
|
|
|
|
|
|
|
|
external :: dgeev,sgeev
|
|
|
|
|
|
|
|
o = om
|
|
|
|
|
|
|
|
! first get the rotation angle
|
|
|
|
t = 0.5_pReal * (math_trace33(om) - 1.0)
|
|
|
|
ax(4) = acos(math_clip(t,-1.0_pReal,1.0_pReal))
|
|
|
|
|
|
|
|
if (dEq0(ax(4))) then
|
|
|
|
ax(1:3) = [ 0.0, 0.0, 1.0 ]
|
|
|
|
else
|
|
|
|
! set some initial LAPACK variables
|
|
|
|
INFO = 0
|
|
|
|
! first initialize the parameters for the LAPACK DGEEV routines
|
|
|
|
LWORK = 20
|
|
|
|
|
|
|
|
! call the eigenvalue solver
|
|
|
|
call dgeev('N','V',3,o,3,Wr,Wi,devNull,3,VR,3,WORK,LWORK,INFO)
|
|
|
|
if (INFO /= 0) call IO_error(0,ext_msg='Error in om2ax DGEEV return not zero')
|
|
|
|
i = maxloc(merge(1.0_pReal,0.0_pReal,cEq(cmplx(Wr,Wi,pReal),cmplx(1.0_pReal,0.0_pReal,pReal),tol=1.0e-14_pReal)),dim=1) ! poor substitute for findloc
|
|
|
|
ax(1:3) = VR(1:3,i)
|
|
|
|
where ( dNeq0([om(2,3)-om(3,2), om(3,1)-om(1,3), om(1,2)-om(2,1)])) &
|
|
|
|
ax(1:3) = sign(ax(1:3),-P *[om(2,3)-om(3,2), om(3,1)-om(1,3), om(1,2)-om(2,1)])
|
|
|
|
endif
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
end function om2ax
|
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert rotation matrix to Rodrigues vector
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function om2ro(om) result(ro)
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(3,3) :: om
|
|
|
|
real(pReal), dimension(4) :: ro
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
ro = eu2ro(om2eu(om))
|
|
|
|
|
|
|
|
end function om2ro
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert rotation matrix to homochoric
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
function om2ho(om) result(ho)
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(3,3) :: om
|
|
|
|
real(pReal), dimension(3) :: ho
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
ho = ax2ho(om2ax(om))
|
|
|
|
|
|
|
|
end function om2ho
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert rotation matrix to cubochoric
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
function om2cu(om) result(cu)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(3,3) :: om
|
|
|
|
real(pReal), dimension(3) :: cu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
cu = ho2cu(om2ho(om))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function om2cu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief Euler angles to unit quaternion
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function eu2qu(eu) result(qu)
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: eu
|
|
|
|
type(quaternion) :: qu
|
|
|
|
real(pReal), dimension(3) :: ee
|
|
|
|
real(pReal) :: cPhi, sPhi
|
|
|
|
|
|
|
|
ee = 0.5_pReal*eu
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
cPhi = cos(ee(2))
|
|
|
|
sPhi = sin(ee(2))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
qu = quaternion([ cPhi*cos(ee(1)+ee(3)), &
|
|
|
|
-P*sPhi*cos(ee(1)-ee(3)), &
|
|
|
|
-P*sPhi*sin(ee(1)-ee(3)), &
|
|
|
|
-P*cPhi*sin(ee(1)+ee(3))])
|
|
|
|
if(qu%w < 0.0_pReal) qu = qu%homomorphed()
|
|
|
|
|
|
|
|
end function eu2qu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief Euler angles to orientation matrix
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function eu2om(eu) result(om)
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: eu
|
|
|
|
real(pReal), dimension(3,3) :: om
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), dimension(3) :: c, s
|
|
|
|
|
|
|
|
c = cos(eu)
|
|
|
|
s = sin(eu)
|
|
|
|
|
|
|
|
om(1,1) = c(1)*c(3)-s(1)*s(3)*c(2)
|
|
|
|
om(1,2) = s(1)*c(3)+c(1)*s(3)*c(2)
|
|
|
|
om(1,3) = s(3)*s(2)
|
|
|
|
om(2,1) = -c(1)*s(3)-s(1)*c(3)*c(2)
|
|
|
|
om(2,2) = -s(1)*s(3)+c(1)*c(3)*c(2)
|
|
|
|
om(2,3) = c(3)*s(2)
|
|
|
|
om(3,1) = s(1)*s(2)
|
|
|
|
om(3,2) = -c(1)*s(2)
|
|
|
|
om(3,3) = c(2)
|
|
|
|
|
|
|
|
where(dEq0(om)) om = 0.0_pReal
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function eu2om
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert euler to axis angle
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function eu2ax(eu) result(ax)
|
|
|
|
|
|
|
|
real(pReal), intent(in), dimension(3) :: eu
|
|
|
|
real(pReal), dimension(4) :: ax
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal) :: t, delta, tau, alpha, sigma
|
|
|
|
|
|
|
|
t = tan(eu(2)*0.5)
|
|
|
|
sigma = 0.5*(eu(1)+eu(3))
|
|
|
|
delta = 0.5*(eu(1)-eu(3))
|
|
|
|
tau = sqrt(t**2+sin(sigma)**2)
|
|
|
|
|
|
|
|
alpha = merge(PI, 2.0*atan(tau/cos(sigma)), dEq(sigma,PI*0.5_pReal,tol=1.0e-15_pReal))
|
|
|
|
|
|
|
|
if (dEq0(alpha)) then ! return a default identity axis-angle pair
|
|
|
|
ax = [ 0.0_pReal, 0.0_pReal, 1.0_pReal, 0.0_pReal ]
|
2019-04-03 16:41:18 +05:30
|
|
|
else
|
2019-04-17 01:47:56 +05:30
|
|
|
ax(1:3) = -P/tau * [ t*cos(delta), t*sin(delta), sin(sigma) ] ! passive axis-angle pair so a minus sign in front
|
|
|
|
ax(4) = alpha
|
|
|
|
if (alpha < 0.0) ax = -ax ! ensure alpha is positive
|
2019-04-03 16:41:18 +05:30
|
|
|
end if
|
2019-04-17 01:47:56 +05:30
|
|
|
|
|
|
|
end function eu2ax
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief Euler angles to Rodrigues vector
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function eu2ro(eu) result(ro)
|
|
|
|
|
|
|
|
real(pReal), intent(in), dimension(3) :: eu
|
|
|
|
real(pReal), dimension(4) :: ro
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
ro = eu2ax(eu)
|
|
|
|
if (ro(4) >= PI) then
|
|
|
|
ro(4) = IEEE_value(ro(4),IEEE_positive_inf)
|
|
|
|
elseif(dEq0(ro(4))) then
|
|
|
|
ro = [ 0.0_pReal, 0.0_pReal, P, 0.0_pReal ]
|
2019-04-03 16:41:18 +05:30
|
|
|
else
|
2019-04-17 01:47:56 +05:30
|
|
|
ro(4) = tan(ro(4)*0.5)
|
2019-04-03 16:41:18 +05:30
|
|
|
end if
|
2019-04-17 01:47:56 +05:30
|
|
|
|
|
|
|
end function eu2ro
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert Euler angles to homochoric
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function eu2ho(eu) result(ho)
|
2019-04-03 16:41:18 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: eu
|
|
|
|
real(pReal), dimension(3) :: ho
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
ho = ax2ho(eu2ax(eu))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function eu2ho
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert Euler angles to cubochoric
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
function eu2cu(eu) result(cu)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: eu
|
2019-04-03 16:41:18 +05:30
|
|
|
real(pReal), dimension(3) :: cu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
cu = ho2cu(eu2ho(eu))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function eu2cu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert axis angle pair to quaternion
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function ax2qu(ax) result(qu)
|
|
|
|
|
|
|
|
real(pReal), intent(in), dimension(4) :: ax
|
|
|
|
type(quaternion) :: qu
|
|
|
|
|
|
|
|
real(pReal) :: c, s
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
if (dEq0(ax(4))) then
|
|
|
|
qu = quaternion([ 1.0_pReal, 0.0_pReal, 0.0_pReal, 0.0_pReal ])
|
|
|
|
else
|
|
|
|
c = cos(ax(4)*0.5)
|
|
|
|
s = sin(ax(4)*0.5)
|
|
|
|
qu = quaternion([ c, ax(1)*s, ax(2)*s, ax(3)*s ])
|
|
|
|
end if
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function ax2qu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert axis angle pair to orientation matrix
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function ax2om(ax) result(om)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(4) :: ax
|
|
|
|
real(pReal), dimension(3,3) :: om
|
|
|
|
|
|
|
|
real(pReal) :: q, c, s, omc
|
|
|
|
integer :: i
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
c = cos(ax(4))
|
|
|
|
s = sin(ax(4))
|
|
|
|
omc = 1.0-c
|
|
|
|
|
|
|
|
forall(i=1:3) om(i,i) = ax(i)**2*omc + c
|
|
|
|
|
|
|
|
q = omc*ax(1)*ax(2)
|
|
|
|
om(1,2) = q + s*ax(3)
|
|
|
|
om(2,1) = q - s*ax(3)
|
|
|
|
|
|
|
|
q = omc*ax(2)*ax(3)
|
|
|
|
om(2,3) = q + s*ax(1)
|
|
|
|
om(3,2) = q - s*ax(1)
|
|
|
|
|
|
|
|
q = omc*ax(3)*ax(1)
|
|
|
|
om(3,1) = q + s*ax(2)
|
|
|
|
om(1,3) = q - s*ax(2)
|
|
|
|
|
|
|
|
if (P > 0.0) om = transpose(om)
|
|
|
|
|
|
|
|
end function ax2om
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert axis angle pair to Euler angles
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function ax2eu(ax) result(eu)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(4) :: ax
|
|
|
|
real(pReal), dimension(3) :: eu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
eu = om2eu(ax2om(ax))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function ax2eu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert axis angle pair to Rodrigues vector
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function ax2ro(ax) result(ro)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(4) :: ax
|
|
|
|
real(pReal), dimension(4) :: ro
|
|
|
|
|
|
|
|
real(pReal), parameter :: thr = 1.0E-7
|
|
|
|
|
|
|
|
if (dEq0(ax(4))) then
|
|
|
|
ro = [ 0.0_pReal, 0.0_pReal, P, 0.0_pReal ]
|
|
|
|
else
|
|
|
|
ro(1:3) = ax(1:3)
|
|
|
|
! we need to deal with the 180 degree case
|
|
|
|
ro(4) = merge(IEEE_value(ro(4),IEEE_positive_inf),tan(ax(4)*0.5 ),abs(ax(4)-PI) < thr)
|
|
|
|
end if
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function ax2ro
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
|
|
|
!> @brief convert axis angle pair to homochoric
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
pure function ax2ho(ax) result(ho)
|
|
|
|
|
|
|
|
real(pReal), intent(in), dimension(4) :: ax
|
|
|
|
real(pReal), dimension(3) :: ho
|
|
|
|
|
|
|
|
real(pReal) :: f
|
|
|
|
|
|
|
|
f = 0.75 * ( ax(4) - sin(ax(4)) )
|
|
|
|
f = f**(1.0/3.0)
|
|
|
|
ho = ax(1:3) * f
|
|
|
|
|
|
|
|
end function ax2ho
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert axis angle pair to cubochoric
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
function ax2cu(ax) result(cu)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(4) :: ax
|
|
|
|
real(pReal), dimension(3) :: cu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
cu = ho2cu(ax2ho(ax))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function ax2cu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert Rodrigues vector to unit quaternion
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function ro2qu(ro) result(qu)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(4) :: ro
|
|
|
|
type(quaternion) :: qu
|
|
|
|
|
|
|
|
qu = ax2qu(ro2ax(ro))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function ro2qu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-02-01 14:31:54 +05:30
|
|
|
!> @brief convert Rodrigues vector to rotation matrix
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
pure function ro2om(ro) result(om)
|
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
real(pReal), intent(in), dimension(4) :: ro
|
|
|
|
real(pReal), dimension(3,3) :: om
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
om = ax2om(ro2ax(ro))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
end function ro2om
|
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert Rodrigues vector to Euler angles
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function ro2eu(ro) result(eu)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(4) :: ro
|
|
|
|
real(pReal), dimension(3) :: eu
|
|
|
|
|
|
|
|
eu = om2eu(ro2om(ro))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function ro2eu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert Rodrigues vector to axis angle pair
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function ro2ax(ro) result(ax)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(4) :: ro
|
|
|
|
real(pReal), dimension(4) :: ax
|
|
|
|
|
|
|
|
real(pReal) :: ta, angle
|
|
|
|
|
|
|
|
ta = ro(4)
|
|
|
|
|
|
|
|
if (dEq0(ta)) then
|
|
|
|
ax = [ 0.0, 0.0, 1.0, 0.0 ]
|
|
|
|
elseif (.not. IEEE_is_finite(ta)) then
|
|
|
|
ax = [ ro(1), ro(2), ro(3), PI ]
|
|
|
|
else
|
|
|
|
angle = 2.0*atan(ta)
|
|
|
|
ta = 1.0/norm2(ro(1:3))
|
|
|
|
ax = [ ro(1)/ta, ro(2)/ta, ro(3)/ta, angle ]
|
|
|
|
end if
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function ro2ax
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert Rodrigues vector to homochoric
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function ro2ho(ro) result(ho)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(4) :: ro
|
|
|
|
real(pReal), dimension(3) :: ho
|
|
|
|
|
|
|
|
real(pReal) :: f
|
|
|
|
|
|
|
|
if (dEq0(norm2(ro(1:3)))) then
|
|
|
|
ho = [ 0.0, 0.0, 0.0 ]
|
|
|
|
else
|
|
|
|
f = merge(2.0*atan(ro(4)) - sin(2.0*atan(ro(4))),PI, IEEE_is_finite(ro(4)))
|
|
|
|
ho = ro(1:3) * (0.75_pReal*f)**(1.0/3.0)
|
|
|
|
end if
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function ro2ho
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert Rodrigues vector to cubochoric
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
function ro2cu(ro) result(cu)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(4) :: ro
|
|
|
|
real(pReal), dimension(3) :: cu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
cu = ho2cu(ro2ho(ro))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function ro2cu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-02-01 14:31:54 +05:30
|
|
|
!> @brief convert homochoric to unit quaternion
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
pure function ho2qu(ho) result(qu)
|
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: ho
|
|
|
|
type(quaternion) :: qu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
qu = ax2qu(ho2ax(ho))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
end function ho2qu
|
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert homochoric to rotation matrix
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function ho2om(ho) result(om)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: ho
|
|
|
|
real(pReal), dimension(3,3) :: om
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
om = ax2om(ho2ax(ho))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function ho2om
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert homochoric to Euler angles
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function ho2eu(ho) result(eu)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: ho
|
|
|
|
real(pReal), dimension(3) :: eu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
eu = ax2eu(ho2ax(ho))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function ho2eu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert homochoric to axis angle pair
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function ho2ax(ho) result(ax)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: ho
|
|
|
|
real(pReal), dimension(4) :: ax
|
|
|
|
|
|
|
|
integer :: i
|
|
|
|
real(pReal) :: hmag_squared, s, hm
|
|
|
|
real(pReal), parameter, dimension(16) :: &
|
|
|
|
tfit = [ 1.0000000000018852_pReal, -0.5000000002194847_pReal, &
|
|
|
|
-0.024999992127593126_pReal, -0.003928701544781374_pReal, &
|
|
|
|
-0.0008152701535450438_pReal, -0.0002009500426119712_pReal, &
|
|
|
|
-0.00002397986776071756_pReal, -0.00008202868926605841_pReal, &
|
|
|
|
+0.00012448715042090092_pReal, -0.0001749114214822577_pReal, &
|
|
|
|
+0.0001703481934140054_pReal, -0.00012062065004116828_pReal, &
|
|
|
|
+0.000059719705868660826_pReal, -0.00001980756723965647_pReal, &
|
|
|
|
+0.000003953714684212874_pReal, -0.00000036555001439719544_pReal ]
|
|
|
|
|
|
|
|
! normalize h and store the magnitude
|
|
|
|
hmag_squared = sum(ho**2.0_pReal)
|
|
|
|
if (dEq0(hmag_squared)) then
|
|
|
|
ax = [ 0.0_pReal, 0.0_pReal, 1.0_pReal, 0.0_pReal ]
|
|
|
|
else
|
|
|
|
hm = hmag_squared
|
|
|
|
|
|
|
|
! convert the magnitude to the rotation angle
|
|
|
|
s = tfit(1) + tfit(2) * hmag_squared
|
|
|
|
do i=3,16
|
|
|
|
hm = hm*hmag_squared
|
|
|
|
s = s + tfit(i) * hm
|
|
|
|
end do
|
|
|
|
ax = [ho/sqrt(hmag_squared), 2.0_pReal*acos(s)]
|
|
|
|
end if
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function ho2ax
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert homochoric to Rodrigues vector
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
pure function ho2ro(ho) result(ro)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: ho
|
|
|
|
real(pReal), dimension(4) :: ro
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
ro = ax2ro(ho2ax(ho))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function ho2ro
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert homochoric to cubochoric
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
function ho2cu(ho) result(cu)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: ho
|
|
|
|
real(pReal), dimension(3) :: cu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-05-17 02:26:48 +05:30
|
|
|
cu = Lambert_BallToCube(ho)
|
2019-04-17 01:47:56 +05:30
|
|
|
|
|
|
|
end function ho2cu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert cubochoric to unit quaternion
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
function cu2qu(cu) result(qu)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: cu
|
2019-04-17 01:47:56 +05:30
|
|
|
type(quaternion) :: qu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
qu = ho2qu(cu2ho(cu))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
end function cu2qu
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-02-01 14:31:54 +05:30
|
|
|
!> @brief convert cubochoric to rotation matrix
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
function cu2om(cu) result(om)
|
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: cu
|
|
|
|
real(pReal), dimension(3,3) :: om
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
om = ho2om(cu2ho(cu))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
end function cu2om
|
|
|
|
|
|
|
|
|
2019-04-17 01:47:56 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
|
|
|
!> @brief convert cubochoric to Euler angles
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
function cu2eu(cu) result(eu)
|
|
|
|
|
|
|
|
real(pReal), intent(in), dimension(3) :: cu
|
|
|
|
real(pReal), dimension(3) :: eu
|
|
|
|
|
|
|
|
eu = ho2eu(cu2ho(cu))
|
|
|
|
|
|
|
|
end function cu2eu
|
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-02-01 14:31:54 +05:30
|
|
|
!> @brief convert cubochoric to axis angle pair
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
function cu2ax(cu) result(ax)
|
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: cu
|
|
|
|
real(pReal), dimension(4) :: ax
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
ax = ho2ax(cu2ho(cu))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
end function cu2ax
|
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-02-01 14:31:54 +05:30
|
|
|
!> @brief convert cubochoric to Rodrigues vector
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
function cu2ro(cu) result(ro)
|
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: cu
|
|
|
|
real(pReal), dimension(4) :: ro
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
ro = ho2ro(cu2ho(cu))
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
end function cu2ro
|
|
|
|
|
|
|
|
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2018-12-08 12:32:55 +05:30
|
|
|
!> @author Marc De Graef, Carnegie Mellon University
|
2019-04-17 01:47:56 +05:30
|
|
|
!> @brief convert cubochoric to homochoric
|
2019-02-01 14:31:54 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-04-17 01:47:56 +05:30
|
|
|
function cu2ho(cu) result(ho)
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-04-03 16:41:18 +05:30
|
|
|
real(pReal), intent(in), dimension(3) :: cu
|
2019-04-17 01:47:56 +05:30
|
|
|
real(pReal), dimension(3) :: ho
|
2018-12-08 12:32:55 +05:30
|
|
|
|
2019-05-17 02:26:48 +05:30
|
|
|
ho = Lambert_CubeToBall(cu)
|
2019-04-17 01:47:56 +05:30
|
|
|
|
|
|
|
end function cu2ho
|
2018-12-08 12:32:55 +05:30
|
|
|
|
|
|
|
|
|
|
|
end module rotations
|