Skip to content
Snippets Groups Projects
Commit d8d61176 authored by WAUTELET Philippe's avatar WAUTELET Philippe
Browse files

Philippe 19/07/2021: eol: replace double precision by real to allow MNH_REAL=4 compilation

parent 100b4f97
No related branches found
No related tags found
No related merge requests found
......@@ -51,6 +51,7 @@ SUBROUTINE EOL_KINE_ALM(KTCOUNT,KTSUBCOUNT,PTSUBSTEP,PTSTEP)
!! -------------
!! Original 04/2017
!! Modification 10/11/20 (PA. Joulin) Updated for a main version
! P. Wautelet 19/07/2021: replace double precision by real to allow MNH_REAL=4 compilation
!!
!!---------------------------------------------------------------
!
......@@ -74,19 +75,19 @@ REAL, INTENT(IN) :: PTSUBSTEP ! sub timestep
REAL, INTENT(IN) :: PTSTEP ! timestep
!
!* 0.3 Local variables
DOUBLE PRECISION, DIMENSION(3,3) :: ZORI_MAT_X, ZORI_MAT_Y, ZORI_MAT_Z
DOUBLE PRECISION, DIMENSION(3) :: ZADD_TO_POS
!
DOUBLE PRECISION, DIMENSION(3) :: ZDIST_TOWO_TELT_RG ! Distance between tower elmt and tower base
DOUBLE PRECISION, DIMENSION(3) :: ZDIST_TOWO_NELT_RG ! Distance between nacelle and base of tower
DOUBLE PRECISION, DIMENSION(3) :: ZDIST_NAC_HUB_RG ! Distance between hub and base of nacelle
DOUBLE PRECISION, DIMENSION(3) :: ZDIST_HUB_BLA_RG ! Distance between blade and base of hub
DOUBLE PRECISION, DIMENSION(3) :: ZDIST_BLA_ELT_RG ! Distance between blade and elements
!
DOUBLE PRECISION, DIMENSION(3) :: ZPOS_ELTLE_RE ! Leading Edge (LE) position, in RE
DOUBLE PRECISION, DIMENSION(3) :: ZPOS_ELTLE_RG ! Leading Edge (LE) position, in RG
DOUBLE PRECISION, DIMENSION(3) :: ZPOS_ELTTE_RE ! Trailing Edge (TE) position, in RE
DOUBLE PRECISION, DIMENSION(3) :: ZPOS_ELTTE_RG ! Trailing Edge (TE) position, in RG
REAL, DIMENSION(3,3) :: ZORI_MAT_X, ZORI_MAT_Y, ZORI_MAT_Z
REAL, DIMENSION(3) :: ZADD_TO_POS
!
REAL, DIMENSION(3) :: ZDIST_TOWO_TELT_RG ! Distance between tower elmt and tower base
REAL, DIMENSION(3) :: ZDIST_TOWO_NELT_RG ! Distance between nacelle and base of tower
REAL, DIMENSION(3) :: ZDIST_NAC_HUB_RG ! Distance between hub and base of nacelle
REAL, DIMENSION(3) :: ZDIST_HUB_BLA_RG ! Distance between blade and base of hub
REAL, DIMENSION(3) :: ZDIST_BLA_ELT_RG ! Distance between blade and elements
!
REAL, DIMENSION(3) :: ZPOS_ELTLE_RE ! Leading Edge (LE) position, in RE
REAL, DIMENSION(3) :: ZPOS_ELTLE_RG ! Leading Edge (LE) position, in RG
REAL, DIMENSION(3) :: ZPOS_ELTTE_RE ! Trailing Edge (TE) position, in RE
REAL, DIMENSION(3) :: ZPOS_ELTTE_RG ! Trailing Edge (TE) position, in RG
!
REAL :: ZTIME ! TIME
INTEGER :: JROT, JBLA, JTELT, JNELT, JBELT ! Loop control
......
......@@ -3,6 +3,9 @@
!MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
!MNH_LIC for details. version 1.
!-----------------------------------------------------------------
! Modifications:
! P. Wautelet 19/07/2021: replace double precision by real to allow MNH_REAL=4 compilation
!-----------------------------------------------------------------
! #######################
MODULE MODI_EOL_MATHS
! #######################
......@@ -10,28 +13,28 @@
INTERFACE
!
FUNCTION CROSS(PA, PB)
DOUBLE PRECISION, DIMENSION(3) :: CROSS
DOUBLE PRECISION, DIMENSION(3), INTENT(IN) :: PA, PB
REAL, DIMENSION(3) :: CROSS
REAL, DIMENSION(3), INTENT(IN) :: PA, PB
END FUNCTION CROSS
!
FUNCTION NORM(PA)
DOUBLE PRECISION :: NORM
DOUBLE PRECISION, DIMENSION(3), INTENT(IN) :: PA
REAL :: NORM
REAL, DIMENSION(3), INTENT(IN) :: PA
END FUNCTION NORM
!
SUBROUTINE GET_ORI_MAT_X(PTHETA, PORI_MAT_X)
DOUBLE PRECISION, INTENT(IN) :: PTHETA ! Angle
DOUBLE PRECISION, DIMENSION(3,3), INTENT(OUT) :: PORI_MAT_X ! Matrix
REAL, INTENT(IN) :: PTHETA ! Angle
REAL, DIMENSION(3,3), INTENT(OUT) :: PORI_MAT_X ! Matrix
END SUBROUTINE GET_ORI_MAT_X
!
SUBROUTINE GET_ORI_MAT_Y(PTHETA, PORI_MAT_Y)
DOUBLE PRECISION, INTENT(IN) :: PTHETA ! Angle
DOUBLE PRECISION, DIMENSION(3,3), INTENT(OUT) :: PORI_MAT_Y ! Matrix
REAL, INTENT(IN) :: PTHETA ! Angle
REAL, DIMENSION(3,3), INTENT(OUT) :: PORI_MAT_Y ! Matrix
END SUBROUTINE GET_ORI_MAT_Y
!
SUBROUTINE GET_ORI_MAT_Z(PTHETA, PORI_MAT_Z)
DOUBLE PRECISION, INTENT(IN) :: PTHETA ! Angle
DOUBLE PRECISION, DIMENSION(3,3), INTENT(OUT) :: PORI_MAT_Z ! Matrix
REAL, INTENT(IN) :: PTHETA ! Angle
REAL, DIMENSION(3,3), INTENT(OUT) :: PORI_MAT_Z ! Matrix
END SUBROUTINE GET_ORI_MAT_Z
!
FUNCTION INTERP_SPLCUB(PAV, PX, PY)
......@@ -71,8 +74,8 @@ END MODULE MODI_EOL_MATHS
FUNCTION CROSS(PA, PB)
! Vectorial product 3D : PA * PB
!
DOUBLE PRECISION, DIMENSION(3) :: CROSS
DOUBLE PRECISION, DIMENSION(3), INTENT(IN) :: PA, PB
REAL, DIMENSION(3) :: CROSS
REAL, DIMENSION(3), INTENT(IN) :: PA, PB
!
CROSS(1) = PA(2) * PB(3) - PA(3) * PB(2)
CROSS(2) = PA(3) * PB(1) - PA(1) * PB(3)
......@@ -85,8 +88,8 @@ END FUNCTION CROSS
FUNCTION NORM(PA)
! Eulerian norm of 3D vector :
!
DOUBLE PRECISION :: NORM
DOUBLE PRECISION, DIMENSION(3), INTENT(IN) :: PA
REAL :: NORM
REAL, DIMENSION(3), INTENT(IN) :: PA
!
NORM = SQRT( PA(1)**2 + PA(2)**2 + PA(3)**2 )
!
......@@ -97,8 +100,8 @@ END FUNCTION NORM
SUBROUTINE GET_ORI_MAT_X(PTHETA, PORI_MAT_X)
! Rotation matrix of PTHETA angle around X
!
DOUBLE PRECISION, INTENT(IN) :: PTHETA ! Angle
DOUBLE PRECISION, DIMENSION(3,3), INTENT(OUT) :: PORI_MAT_X ! Matrix
REAL, INTENT(IN) :: PTHETA ! Angle
REAL, DIMENSION(3,3), INTENT(OUT) :: PORI_MAT_X ! Matrix
!
PORI_MAT_X (1,1) = 1d0
PORI_MAT_X (1,2) = 0d0
......@@ -117,8 +120,8 @@ END SUBROUTINE GET_ORI_MAT_X
SUBROUTINE GET_ORI_MAT_Y(PTHETA, PORI_MAT_Y)
! Rotation matrix of PTHETA angle around Y
!
DOUBLE PRECISION, INTENT(IN) :: PTHETA ! Angle
DOUBLE PRECISION, DIMENSION(3,3), INTENT(OUT) :: PORI_MAT_Y ! Matrix
REAL, INTENT(IN) :: PTHETA ! Angle
REAL, DIMENSION(3,3), INTENT(OUT) :: PORI_MAT_Y ! Matrix
!
PORI_MAT_Y (1,1) = +COS(PTHETA)
PORI_MAT_Y (1,2) = 0d0
......@@ -137,8 +140,8 @@ END SUBROUTINE GET_ORI_MAT_Y
SUBROUTINE GET_ORI_MAT_Z(PTHETA, PORI_MAT_Z)
! Rotation matrix of PTHETA angle around Z
!
DOUBLE PRECISION, INTENT(IN) :: PTHETA ! Angle
DOUBLE PRECISION, DIMENSION(3,3), INTENT(OUT) :: PORI_MAT_Z ! Matrix
REAL, INTENT(IN) :: PTHETA ! Angle
REAL, DIMENSION(3,3), INTENT(OUT) :: PORI_MAT_Z ! Matrix
!
PORI_MAT_Z (1,1) = +COS(PTHETA)
PORI_MAT_Z (1,2) = -SIN(PTHETA)
......
......@@ -22,6 +22,7 @@
!! MODIFICATIONS
!! -------------
!! Original 04/18
! P. Wautelet 19/07/2021: replace double precision by real to allow MNH_REAL=4 compilation
!!
!-----------------------------------------------------------------------------
!
......@@ -30,79 +31,79 @@
!
!
! - Matrix to move from one fram to an other -
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XMAT_RG_RT ! RG = Repere GLOBAL, RT = Repere TOWER
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XMAT_RG_RN, XMAT_RT_RN ! RN = Repere NACELLE
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XMAT_RG_RH, XMAT_RH_RG, XMAT_RN_RH ! RH = Repere HUB
DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE :: XMAT_RG_RB, XMAT_RH_RB ! RB = Repere BLADE
DOUBLE PRECISION, DIMENSION(:,:,:,:,:), ALLOCATABLE :: XMAT_RG_RE, XMAT_RE_RG, XMAT_RB_RE ! RE = Repere ELEMENT
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XMAT_RG_RT ! RG = Repere GLOBAL, RT = Repere TOWER
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XMAT_RG_RN, XMAT_RT_RN ! RN = Repere NACELLE
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XMAT_RG_RH, XMAT_RH_RG, XMAT_RN_RH ! RH = Repere HUB
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: XMAT_RG_RB, XMAT_RH_RB ! RB = Repere BLADE
REAL, DIMENSION(:,:,:,:,:), ALLOCATABLE :: XMAT_RG_RE, XMAT_RE_RG, XMAT_RB_RE ! RE = Repere ELEMENT
! - POSITIONS & ORIENTATIONS -
DOUBLE PRECISION, DIMENSION(3) :: XPOS_REF ! Reference position
REAL, DIMENSION(3) :: XPOS_REF ! Reference position
! Tower
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XPOSINI_TOWO_RG ! Initial tower origin position, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XPOS_TOWO_RG ! Current tower origin real position, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XPOS_TELT_RG ! Current tower element position, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XPOS_TELT_RT ! Current tower element position, in tower frame
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XANGINI_TOW_RG ! Initial tower orientation in global ref frame
REAL, DIMENSION(:,:), ALLOCATABLE :: XPOSINI_TOWO_RG ! Initial tower origin position, in global reference frame
REAL, DIMENSION(:,:), ALLOCATABLE :: XPOS_TOWO_RG ! Current tower origin real position, in global reference frame
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XPOS_TELT_RG ! Current tower element position, in global reference frame
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XPOS_TELT_RT ! Current tower element position, in tower frame
REAL, DIMENSION(:,:), ALLOCATABLE :: XANGINI_TOW_RG ! Initial tower orientation in global ref frame
! Nacelle
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XPOSINI_NACO_RT ! Initial nacelle position, in tower reference frame
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XPOS_NACO_RG ! Initial nacelle position, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XPOS_NELT_RG ! Initial nacelle position, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XPOS_NELT_RN ! Initial nacelle position, in nacelle reference frame
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XANGINI_NAC_RT ! Initial nacelle orientation, in tower reference frame
REAL, DIMENSION(:,:), ALLOCATABLE :: XPOSINI_NACO_RT ! Initial nacelle position, in tower reference frame
REAL, DIMENSION(:,:), ALLOCATABLE :: XPOS_NACO_RG ! Initial nacelle position, in global reference frame
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XPOS_NELT_RG ! Initial nacelle position, in global reference frame
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XPOS_NELT_RN ! Initial nacelle position, in nacelle reference frame
REAL, DIMENSION(:,:), ALLOCATABLE :: XANGINI_NAC_RT ! Initial nacelle orientation, in tower reference frame
! Hub
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XPOSINI_HUB_RN ! Initial hub position, in nacelle reference frame
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XPOS_HUB_RG ! Current hub position, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XANGINI_HUB_RN ! Initial hub orientation, in nacelle reference frame
REAL, DIMENSION(:,:), ALLOCATABLE :: XPOSINI_HUB_RN ! Initial hub position, in nacelle reference frame
REAL, DIMENSION(:,:), ALLOCATABLE :: XPOS_HUB_RG ! Current hub position, in global reference frame
REAL, DIMENSION(:,:), ALLOCATABLE :: XANGINI_HUB_RN ! Initial hub orientation, in nacelle reference frame
! Blade
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XPOSINI_BLA_RH ! Initial blade root position, in hub reference frame
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XPOS_BLA_RG ! Current blade root position, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XANGINI_BLA_RH ! Initial blade orientation, in hub reference frame
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XPOSINI_BLA_RH ! Initial blade root position, in hub reference frame
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XPOS_BLA_RG ! Current blade root position, in global reference frame
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XANGINI_BLA_RH ! Initial blade orientation, in hub reference frame
! Element
DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE :: XPOS_ELT_RB ! Element position, in blade reference frame
DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE :: XPOS_ELT_RG ! Element position, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE :: XPOS_SEC_RB ! Section position, in blade reference frame
DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE :: XPOS_SEC_RG ! Section position, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE :: XANGINI_ELT_RB ! Initial element orientation in blade reference frame
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XTWIST_ELT ! Element twist, interpolated from data
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XCHORD_ELT ! Element chord lenght, interpolated from data
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XSURF_ELT ! Element lift surface
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: XPOS_ELT_RB ! Element position, in blade reference frame
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: XPOS_ELT_RG ! Element position, in global reference frame
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: XPOS_SEC_RB ! Section position, in blade reference frame
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: XPOS_SEC_RG ! Section position, in global reference frame
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: XANGINI_ELT_RB ! Initial element orientation in blade reference frame
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XTWIST_ELT ! Element twist, interpolated from data
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XCHORD_ELT ! Element chord lenght, interpolated from data
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XSURF_ELT ! Element lift surface
!
!
! - STRUCTURAL VELOCITIES -
! Tower
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XTVEL_TOWO_RG ! Tower base translation velocity, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XTVEL_TELT_RG ! Tower element velocity, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XRVEL_RT_RG ! RT/RG rotational velocity
REAL, DIMENSION(:,:), ALLOCATABLE :: XTVEL_TOWO_RG ! Tower base translation velocity, in global reference frame
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XTVEL_TELT_RG ! Tower element velocity, in global reference frame
REAL, DIMENSION(:,:), ALLOCATABLE :: XRVEL_RT_RG ! RT/RG rotational velocity
! Nacelle
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XTVEL_NACO_RT ! Nacelle base translation velocity, in tower reference frame
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XTVEL_NELT_RG ! Nacelle element translation velocity, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XRVEL_RN_RT ! RN/RT rotational velocity
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XRVEL_RN_RG ! RN/RG rotational velocity
REAL, DIMENSION(:,:), ALLOCATABLE :: XTVEL_NACO_RT ! Nacelle base translation velocity, in tower reference frame
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XTVEL_NELT_RG ! Nacelle element translation velocity, in global reference frame
REAL, DIMENSION(:,:), ALLOCATABLE :: XRVEL_RN_RT ! RN/RT rotational velocity
REAL, DIMENSION(:,:), ALLOCATABLE :: XRVEL_RN_RG ! RN/RG rotational velocity
! Hub
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XTVEL_HUB_RN ! Hub base translation velocity, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XTVEL_HUB_RG ! Hub base translation velocity, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XRVEL_RH_RN ! RH/RN rotational velocity
DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: XRVEL_RH_RG ! RH/RG rotational velocity
REAL, DIMENSION(:,:), ALLOCATABLE :: XTVEL_HUB_RN ! Hub base translation velocity, in global reference frame
REAL, DIMENSION(:,:), ALLOCATABLE :: XTVEL_HUB_RG ! Hub base translation velocity, in global reference frame
REAL, DIMENSION(:,:), ALLOCATABLE :: XRVEL_RH_RN ! RH/RN rotational velocity
REAL, DIMENSION(:,:), ALLOCATABLE :: XRVEL_RH_RG ! RH/RG rotational velocity
! Blade
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XTVEL_BLA_RH ! Blade base translation velocity, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XTVEL_BLA_RG ! Blade base translation velocity, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XRVEL_RB_RH ! RB/RH rotational velocity
DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: XRVEL_RB_RG ! RB/RG rotational velocity
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XTVEL_BLA_RH ! Blade base translation velocity, in global reference frame
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XTVEL_BLA_RG ! Blade base translation velocity, in global reference frame
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XRVEL_RB_RH ! RB/RH rotational velocity
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XRVEL_RB_RG ! RB/RG rotational velocity
! Elements
DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE :: XTVEL_ELT_RB ! Element base translation velocity, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE :: XTVEL_ELT_RG ! Element base translation velocity, in global reference frame
DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE :: XTVEL_ELT_RE ! Element base translation velocity, in element reference frame
DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE :: XRVEL_RE_RB ! RE/RB rotational velocity
DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE :: XRVEL_RE_RG ! RE/RG rotational velocity
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: XTVEL_ELT_RB ! Element base translation velocity, in global reference frame
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: XTVEL_ELT_RG ! Element base translation velocity, in global reference frame
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: XTVEL_ELT_RE ! Element base translation velocity, in element reference frame
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: XRVEL_RE_RB ! RE/RB rotational velocity
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: XRVEL_RE_RG ! RE/RG rotational velocity
END MODULE MODD_EOL_KINE_ALM
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment