Yes sure. y compiler gives the following error:
module_cords.f90:10:4:
type point(k)
1
Error: Unclassifiable statement at (1)
module_cords.f90:11:14:
integer, kind :: k = kind(0.)
1
Error: Invalid character in name at (1)
module_cords.f90:12:17:
real(kind=k) :: x,y,z
1
Error: Symbol ‘k’ at (1) has no IMPLICIT type
module_cords.f90:14:7:
procedure,private :: pointplus, pointminus, pointseparation
1
Error: Unclassifiable statement at (1)
module_cords.f90:15:7:
procedure,private :: vecotr_dot, vecotr_cros
1
Error: Unclassifiable statement at (1)
module_cords.f90:16:7:
procedure,private :: point_multiply_vct_scalar_32, point_multiply_vct_scalar_64
1
Error: Unclassifiable statement at (1)
module_cords.f90:17:7:
procedure,private :: point_multiply_scalar_vct_32, point_multiply_scalar_vct_64
1
Error: Unclassifiable statement at (1)
module_cords.f90:18:7:
procedure,private,pass(this) :: absvec_real32, absvec_real64
1
Error: Unclassifiable statement at (1)
module_cords.f90:19:7:
generic,public :: operator(+) => pointplus
1
Error: Unclassifiable statement at (1)
module_cords.f90:20:7:
generic,public :: operator(-) => pointminus
1
Error: Unclassifiable statement at (1)
module_cords.f90:21:7:
generic,public :: operator(*) => point_multiply_vct_scalar_32, point_multiply_vct_scalar_64
1
Error: Unclassifiable statement at (1)
module_cords.f90:22:7:
generic,public :: operator(*) => point_multiply_scalar_vct_32, point_multiply_scalar_vct_64
1
Error: Unclassifiable statement at (1)
module_cords.f90:23:7:
generic,public :: operator(.distance.) => pointseparation
1
Error: Unclassifiable statement at (1)
module_cords.f90:24:7:
generic,public :: assignment(=) => absvec_real32, absvec_real64
1
Error: Unclassifiable statement at (1)
module_cords.f90:25:7:
generic,public :: operator(.dot.) => vecotr_dot
1
Error: Unclassifiable statement at (1)
module_cords.f90:26:7:
generic,public :: operator(.cros.) => vecotr_cros
1
Error: Unclassifiable statement at (1)
module_cords.f90:27:7:
end type point
1
Error: Expecting END MODULE statement at (1)
module_cords.f90:29:24:
type, extends(point) :: pointT
1
Error: Symbol ‘point’ at (1) has not been previously defined
module_cords.f90:30:18:
real, PUBLIC :: T
1
Error: PUBLIC attribute at (1) is not allowed outside of the specification part of a module
module_cords.f90:31:14:
contains
1
Error: Unexpected CONTAINS statement in CONTAINS section at (1)
module_cords.f90:32:6:
procedure,PRIVATE :: Tplus,Tminus
1
Error: Unclassifiable statement at (1)
module_cords.f90:33:7:
end type pointT
1
Error: Expecting END MODULE statement at (1)
module_cords.f90:35:24:
type, extends(point) :: point_64
1
Error: Symbol ‘point’ at (1) has not been previously defined
module_cords.f90:36:25:
real(real64),PUBLIC :: x_64, y_64, z_64
1
Error: PUBLIC attribute at (1) is not allowed outside of the specification part of a module
module_cords.f90:37:7:
end type point_64
1
Error: Expecting END MODULE statement at (1)
module_cords.f90:39:20:
interface absvec
1
Error: Unexpected INTERFACE statement in CONTAINS section at (1)
module_cords.f90:40:22:
module procedure absvec_real32, absvec_real64
1
Error: MODULE PROCEDURE at (1) must be in a generic module interface
module_cords.f90:41:7:
end interface absvec
1
Error: Expecting END MODULE statement at (1)
module_cords.f90:43:10:
contains
1
Error: Unexpected CONTAINS statement in CONTAINS section at (1)
module_cords.f90:45:19:
class(pointT),intent(in) :: this, b
1
Error: Derived type ‘pointt’ at (1) is being used before it is defined
module_cords.f90:46:11:
Tplus%x = this%T + b%T
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:50:19:
class(pointT),intent(in) :: this, b
1
Error: Derived type ‘pointt’ at (1) is being used before it is defined
module_cords.f90:51:12:
Tminus%x = this%T - b%T
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:55:18:
class(point),intent(in) :: this, b
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:56:15:
pointplus%x = this%x + b%x
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:57:15:
pointplus%y = this%y + b%y
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:58:15:
pointplus%z = this%z + b%z
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:62:18:
class(point),intent(in) :: this
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:64:34:
point_multiply_vct_scalar_32%x = this%x * scalar
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:65:34:
point_multiply_vct_scalar_32%y = this%y * scalar
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:66:34:
point_multiply_vct_scalar_32%z = this%z * scalar
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:70:18:
class(point),intent(in) :: this
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:72:34:
point_multiply_scalar_vct_32%x = this%x * scalar
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:73:34:
point_multiply_scalar_vct_32%y = this%y * scalar
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:74:34:
point_multiply_scalar_vct_32%z = this%z * scalar
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:78:18:
class(point),intent(in) :: this
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:77:4:
type(point_64) function point_multiply_vct_scalar_64(this,scalar) ! for +
1
Error: The type for function ‘point_multiply_vct_scalar_64’ at (1) is not accessible
module_cords.f90:77:4:
type(point_64) function point_multiply_vct_scalar_64(this,scalar) ! for +
1
Error: Function result ‘point_multiply_vct_scalar_64’ at (1) has no IMPLICIT type
module_cords.f90:82:20:
class is (point_64)
1
Error: Syntax error in CLASS IS specification at (1)
module_cords.f90:83:43:
point_multiply_vct_scalar_64%x = this%x_64 * scalar
1
Error: Symbol ‘point_multiply_vct_scalar_64’ at (1) has no IMPLICIT type
module_cords.f90:84:43:
point_multiply_vct_scalar_64%y = this%y_64 * scalar
1
Error: Symbol ‘point_multiply_vct_scalar_64’ at (1) has no IMPLICIT type
module_cords.f90:85:43:
point_multiply_vct_scalar_64%z = this%z_64 * scalar
1
Error: Symbol ‘point_multiply_vct_scalar_64’ at (1) has no IMPLICIT type
module_cords.f90:87:43:
point_multiply_vct_scalar_64%x = this%x * scalar
1
Error: Symbol ‘point_multiply_vct_scalar_64’ at (1) has no IMPLICIT type
module_cords.f90:88:43:
point_multiply_vct_scalar_64%y = this%y * scalar
1
Error: Symbol ‘point_multiply_vct_scalar_64’ at (1) has no IMPLICIT type
module_cords.f90:89:43:
point_multiply_vct_scalar_64%z = this%z * scalar
1
Error: Symbol ‘point_multiply_vct_scalar_64’ at (1) has no IMPLICIT type
module_cords.f90:95:18:
class(point),intent(in) :: this
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:99:20:
class is (point_64)
1
Error: Syntax error in CLASS IS specification at (1)
module_cords.f90:100:40:
point_multiply_scalar_vct_64%x = this%x_64 * scalar
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:101:40:
point_multiply_scalar_vct_64%y = this%y_64 * scalar
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:102:40:
point_multiply_scalar_vct_64%z = this%z_64 * scalar
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:107:18:
class(point),intent(in):: this, b
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:109:16:
pointminus%x = this%x - b%x
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:110:16:
pointminus%y = this%y - b%y
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:111:16:
pointminus%z = this%z - b%z
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:115:18:
class(point),intent(in) :: this,b
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:118:17:
(this%x-b%x)**2+(this%y-b%y)**2+(this%z-b%z)**2)
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:123:18:
class(point),intent(in) :: this
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:124:20:
a = sqrt(this%x**2+this%y**2+this%z**2)
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:129:18:
class(point),intent(in) :: this
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:130:20:
a = sqrt(this%x**2 + this%y**2 + this%z**2)
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:134:18:
class(point),intent(in) :: this,b
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:135:25:
vecotr_dot = (this%x*b%x)+(this%y*b%y)+(this%z*b%z)
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:139:18:
class(point),intent(in):: this, b
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:141:17:
vecotr_cros%x = this%y * b%z - this%z * b%y
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:142:17:
vecotr_cros%y = this%z * b%x - this%x * b%z
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:143:17:
vecotr_cros%z = this%x * b%y - this%y * b%x
1
Error: Derived type ‘point’ at (1) is being used before it is defined
module_cords.f90:127:35:
subroutine absvec_real32(a,this) ! for = (distance
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:121:35:
subroutine absvec_real64(a,this) ! for = (distance
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:69:65:
type(point) function point_multiply_scalar_vct_32(scalar,this) ! for +
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:94:65:
type(point) function point_multiply_scalar_vct_64(scalar,this) ! for +
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:61:58:
type(point) function point_multiply_vct_scalar_32(this,scalar) ! for +
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:77:61:
type(point_64) function point_multiply_vct_scalar_64(this,scalar) ! for +
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:106:40:
type(point) function pointminus(this,b) ! for -
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:106:42:
type(point) function pointminus(this,b) ! for -
1
Error: Symbol ‘b’ at (1) has no IMPLICIT type
module_cords.f90:54:39:
type(point) function pointplus(this,b) ! for +
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:54:41:
type(point) function pointplus(this,b) ! for +
1
Error: Symbol ‘b’ at (1) has no IMPLICIT type
module_cords.f90:114:38:
real function pointseparation(this,b) ! for .distance.
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:114:40:
real function pointseparation(this,b) ! for .distance.
1
Error: Symbol ‘b’ at (1) has no IMPLICIT type
module_cords.f90:49:36:
type(point) function Tminus(this,b) ! for +
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:49:38:
type(point) function Tminus(this,b) ! for +
1
Error: Symbol ‘b’ at (1) has no IMPLICIT type
module_cords.f90:44:35:
type(point) function Tplus(this,b) ! for +
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:44:37:
type(point) function Tplus(this,b) ! for +
1
Error: Symbol ‘b’ at (1) has no IMPLICIT type
module_cords.f90:138:41:
type(point) function vecotr_cros(this,b) ! for -
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:138:43:
type(point) function vecotr_cros(this,b) ! for -
1
Error: Symbol ‘b’ at (1) has no IMPLICIT type
module_cords.f90:133:33:
real function vecotr_dot(this,b) ! for .distance.
1
Error: Symbol ‘this’ at (1) has no IMPLICIT type
module_cords.f90:133:35:
real function vecotr_dot(this,b) ! for .distance.
1
Error: Symbol ‘b’ at (1) has no IMPLICIT type
module_cords.f90:69:53:
type(point) function point_multiply_scalar_vct_32(scalar,this) ! for +
1
Error: The derived type ‘point_multiply_scalar_vct_32’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:94:53:
type(point) function point_multiply_scalar_vct_64(scalar,this) ! for +
1
Error: The derived type ‘point_multiply_scalar_vct_64’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:61:53:
type(point) function point_multiply_vct_scalar_32(this,scalar) ! for +
1
Error: The derived type ‘point_multiply_vct_scalar_32’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:106:35:
type(point) function pointminus(this,b) ! for -
1
Error: The derived type ‘pointminus’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:54:34:
type(point) function pointplus(this,b) ! for +
1
Error: The derived type ‘pointplus’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:49:31:
type(point) function Tminus(this,b) ! for +
1
Error: The derived type ‘tminus’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:44:30:
type(point) function Tplus(this,b) ! for +
1
Error: The derived type ‘tplus’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:138:36:
type(point) function vecotr_cros(this,b) ! for -
1
Error: The derived type ‘vecotr_cros’ at (1) is of type ‘point’, which has not been defined
module_cords.f90:138:36:
type(point) function vecotr_cros(this,b) ! for -
1
Error: Function ‘vecotr_cros’ at (1) has no IMPLICIT type
module_cords.f90:106:35:
type(point) function pointminus(this,b) ! for -
1
Error: Function ‘pointminus’ at (1) has no IMPLICIT type
module_cords.f90:94:53:
type(point) function point_multiply_scalar_vct_64(scalar,this) ! for +
1
Error: Function ‘point_multiply_scalar_vct_64’ at (1) has no IMPLICIT type
module_cords.f90:69:53:
type(point) function point_multiply_scalar_vct_32(scalar,this) ! for +
1
Error: Function ‘point_multiply_scalar_vct_32’ at (1) has no IMPLICIT type
module_cords.f90:61:53:
type(point) function point_multiply_vct_scalar_32(this,scalar) ! for +
1
Error: Function ‘point_multiply_vct_scalar_32’ at (1) has no IMPLICIT type
module_cords.f90:54:34:
type(point) function pointplus(this,b) ! for +
1
Error: Function ‘pointplus’ at (1) has no IMPLICIT type
module_cords.f90:49:31:
type(point) function Tminus(this,b) ! for +
1
Error: Function ‘tminus’ at (1) has no IMPLICIT type
module_cords.f90:44:30:
type(point) function Tplus(this,b) ! for +
1
Error: Function ‘tplus’ at (1) has no IMPLICIT type
module_cords.f90:98:24:
select type (this)
1
Error: Selector shall be polymorphic in SELECT TYPE statement at (1)
module_cords.f90:81:24:
select type (this)
1
Error: Selector shall be polymorphic in SELECT TYPE statement at (1)
exercise_10_1.f90:2:8:
use coords
1
And my module looks as follows:
module coords
use iso_fortran_env
implicit none
private
public :: point
type point(k)
integer, kind :: k = kind(0.)
real(kind=k) :: x,y,z
contains
procedure,private :: pointplus, pointminus, pointseparation
procedure,private :: vecotr_dot, vecotr_cros
procedure,private :: point_multiply_vct_scalar_32, point_multiply_vct_scalar_64
procedure,private :: point_multiply_scalar_vct_32, point_multiply_scalar_vct_64
procedure,private,pass(this) :: absvec_real32, absvec_real64
generic,public :: operator(+) => pointplus
generic,public :: operator(-) => pointminus
generic,public :: operator(*) => point_multiply_vct_scalar_32, point_multiply_vct_scalar_64
generic,public :: operator(*) => point_multiply_scalar_vct_32, point_multiply_scalar_vct_64
generic,public :: operator(.distance.) => pointseparation
generic,public :: assignment(=) => absvec_real32, absvec_real64
generic,public :: operator(.dot.) => vecotr_dot
generic,public :: operator(.cros.) => vecotr_cros
end type point
type, extends(point) :: pointT
real, PUBLIC :: T
contains
procedure,PRIVATE :: Tplus,Tminus
end type pointT
type, extends(point) :: point_64
real(real64),PUBLIC :: x_64, y_64, z_64
end type point_64
interface absvec
module procedure absvec_real32, absvec_real64
end interface absvec
contains
type(point) function Tplus(this,b) ! for +
class(pointT),intent(in) :: this, b
Tplus%x = this%T + b%T
end function Tplus
type(point) function Tminus(this,b) ! for +
class(pointT),intent(in) :: this, b
Tminus%x = this%T - b%T
end function Tminus
type(point) function pointplus(this,b) ! for +
class(point),intent(in) :: this, b
pointplus%x = this%x + b%x
pointplus%y = this%y + b%y
pointplus%z = this%z + b%z
end function pointplus
type(point) function point_multiply_vct_scalar_32(this,scalar) ! for +
class(point),intent(in) :: this
real(real32), INTENT(IN) :: scalar
point_multiply_vct_scalar_32%x = this%x * scalar
point_multiply_vct_scalar_32%y = this%y * scalar
point_multiply_vct_scalar_32%z = this%z * scalar
end function point_multiply_vct_scalar_32
type(point) function point_multiply_scalar_vct_32(scalar,this) ! for +
class(point),intent(in) :: this
real(real32), INTENT(IN) :: scalar
point_multiply_scalar_vct_32%x = this%x * scalar
point_multiply_scalar_vct_32%y = this%y * scalar
point_multiply_scalar_vct_32%z = this%z * scalar
end function point_multiply_scalar_vct_32
type(point_64) function point_multiply_vct_scalar_64(this,scalar) ! for +
class(point),intent(in) :: this
real(real64), INTENT(IN) :: scalar
select type (this)
class is (point_64)
point_multiply_vct_scalar_64%x = this%x_64 * scalar
point_multiply_vct_scalar_64%y = this%y_64 * scalar
point_multiply_vct_scalar_64%z = this%z_64 * scalar
class is (point)
point_multiply_vct_scalar_64%x = this%x * scalar
point_multiply_vct_scalar_64%y = this%y * scalar
point_multiply_vct_scalar_64%z = this%z * scalar
end select
end function point_multiply_vct_scalar_64
type(point) function point_multiply_scalar_vct_64(scalar,this) ! for +
class(point),intent(in) :: this
real(real64), INTENT(IN) :: scalar
select type (this)
class is (point_64)
point_multiply_scalar_vct_64%x = this%x_64 * scalar
point_multiply_scalar_vct_64%y = this%y_64 * scalar
point_multiply_scalar_vct_64%z = this%z_64 * scalar
end select
end function point_multiply_scalar_vct_64
type(point) function pointminus(this,b) ! for -
class(point),intent(in):: this, b
pointminus%x = this%x - b%x
pointminus%y = this%y - b%y
pointminus%z = this%z - b%z
end function pointminus
real function pointseparation(this,b) ! for .distance.
class(point),intent(in) :: this,b
pointseparation = sqrt( &
(this%x-b%x)**2+(this%y-b%y)**2+(this%z-b%z)**2)
end function pointseparation
subroutine absvec_real64(a,this) ! for = (distance
real(real64),intent(out) :: a ! from origin)
class(point),intent(in) :: this
a = sqrt(this%x**2+this%y**2+this%z**2)
end subroutine absvec_real64
subroutine absvec_real32(a,this) ! for = (distance
real(real32),intent(out) :: a ! from origin)
class(point),intent(in) :: this
a = sqrt(this%x**2 + this%y**2 + this%z**2)
end subroutine absvec_real32
real function vecotr_dot(this,b) ! for .distance.
class(point),intent(in) :: this,b
vecotr_dot = (this%x*b%x)+(this%y*b%y)+(this%z*b%z)
end function vecotr_dot
type(point) function vecotr_cros(this,b) ! for -
class(point),intent(in):: this, b
vecotr_cros%x = this%y * b%z - this%z * b%y
vecotr_cros%y = this%z * b%x - this%x * b%z
vecotr_cros%z = this%x * b%y - this%y * b%x
end function vecotr_cros
end module coords