Skip to content

Commit

Permalink
stat_dev: add rank 3
Browse files Browse the repository at this point in the history
  • Loading branch information
jvdp1 committed Jan 20, 2020
1 parent 60ab523 commit 7612613
Show file tree
Hide file tree
Showing 5 changed files with 533 additions and 6 deletions.
90 changes: 90 additions & 0 deletions src/stdlib_experimental_stat.f90
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@ module function mean_1_int64_dp(x) result(res)
real(dp) :: res
end function mean_1_int64_dp


module function mean_2_all_sp_sp(x) result(res)
real(sp), intent(in) :: x(:,:)
real(sp) :: res
Expand Down Expand Up @@ -109,6 +110,95 @@ module function mean_2_int64_dp(x, dim) result(res)
real(dp) :: res(size(x)/size(x, dim))
end function mean_2_int64_dp


module function mean_3_all_sp_sp(x) result(res)
real(sp), intent(in) :: x(:,:,:)
real(sp) :: res
end function mean_3_all_sp_sp
module function mean_3_all_dp_dp(x) result(res)
real(dp), intent(in) :: x(:,:,:)
real(dp) :: res
end function mean_3_all_dp_dp
module function mean_3_all_qp_qp(x) result(res)
real(qp), intent(in) :: x(:,:,:)
real(qp) :: res
end function mean_3_all_qp_qp

module function mean_3_all_int8_dp(x) result(res)
integer(int8), intent(in) :: x(:,:,:)
real(dp) :: res
end function mean_3_all_int8_dp
module function mean_3_all_int16_dp(x) result(res)
integer(int16), intent(in) :: x(:,:,:)
real(dp) :: res
end function mean_3_all_int16_dp
module function mean_3_all_int32_dp(x) result(res)
integer(int32), intent(in) :: x(:,:,:)
real(dp) :: res
end function mean_3_all_int32_dp
module function mean_3_all_int64_dp(x) result(res)
integer(int64), intent(in) :: x(:,:,:)
real(dp) :: res
end function mean_3_all_int64_dp

module function mean_3_sp_sp(x, dim) result(res)
real(sp), intent(in) :: x(:,:,:)
integer, intent(in) :: dim
integer :: j_
real(sp) :: res( &
merge(size(x,2),size(x,1),mask = any((/(j_, j_ = dim, 3)/) == 1)), &
merge(size(x,3),size(x,2),mask = any((/(j_, j_ = dim, 3)/) == 2)) )
end function mean_3_sp_sp
module function mean_3_dp_dp(x, dim) result(res)
real(dp), intent(in) :: x(:,:,:)
integer, intent(in) :: dim
integer :: j_
real(dp) :: res( &
merge(size(x,2),size(x,1),mask = any((/(j_, j_ = dim, 3)/) == 1)), &
merge(size(x,3),size(x,2),mask = any((/(j_, j_ = dim, 3)/) == 2)) )
end function mean_3_dp_dp
module function mean_3_qp_qp(x, dim) result(res)
real(qp), intent(in) :: x(:,:,:)
integer, intent(in) :: dim
integer :: j_
real(qp) :: res( &
merge(size(x,2),size(x,1),mask = any((/(j_, j_ = dim, 3)/) == 1)), &
merge(size(x,3),size(x,2),mask = any((/(j_, j_ = dim, 3)/) == 2)) )
end function mean_3_qp_qp

module function mean_3_int8_dp(x, dim) result(res)
integer(int8), intent(in) :: x(:,:,:)
integer, intent(in) :: dim
integer :: j_
real(dp) :: res( &
merge(size(x,2),size(x,1),mask = any((/(j_, j_ = dim, 3)/) == 1)), &
merge(size(x,3),size(x,2),mask = any((/(j_, j_ = dim, 3)/) == 2)) )
end function mean_3_int8_dp
module function mean_3_int16_dp(x, dim) result(res)
integer(int16), intent(in) :: x(:,:,:)
integer, intent(in) :: dim
integer :: j_
real(dp) :: res( &
merge(size(x,2),size(x,1),mask = any((/(j_, j_ = dim, 3)/) == 1)), &
merge(size(x,3),size(x,2),mask = any((/(j_, j_ = dim, 3)/) == 2)) )
end function mean_3_int16_dp
module function mean_3_int32_dp(x, dim) result(res)
integer(int32), intent(in) :: x(:,:,:)
integer, intent(in) :: dim
integer :: j_
real(dp) :: res( &
merge(size(x,2),size(x,1),mask = any((/(j_, j_ = dim, 3)/) == 1)), &
merge(size(x,3),size(x,2),mask = any((/(j_, j_ = dim, 3)/) == 2)) )
end function mean_3_int32_dp
module function mean_3_int64_dp(x, dim) result(res)
integer(int64), intent(in) :: x(:,:,:)
integer, intent(in) :: dim
integer :: j_
real(dp) :: res( &
merge(size(x,2),size(x,1),mask = any((/(j_, j_ = dim, 3)/) == 1)), &
merge(size(x,3),size(x,2),mask = any((/(j_, j_ = dim, 3)/) == 2)) )
end function mean_3_int64_dp

end interface

end module
38 changes: 38 additions & 0 deletions src/stdlib_experimental_stat.fypp.f90
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ module function mean_1_${k1}$_dp(x) result(res)
end function mean_1_${k1}$_dp
#:endfor


#:for i1, k1, t1 in iktr
module function mean_2_all_${k1}$_${k1}$(x) result(res)
${t1}$, intent(in) :: x(:,:)
Expand Down Expand Up @@ -62,6 +63,43 @@ module function mean_2_${k1}$_dp(x, dim) result(res)
end function mean_2_${k1}$_dp
#:endfor


#:for i1, k1, t1 in iktr
module function mean_3_all_${k1}$_${k1}$(x) result(res)
${t1}$, intent(in) :: x(:,:,:)
${t1}$ :: res
end function mean_3_all_${k1}$_${k1}$
#:endfor

#:for i1, k1, t1 in ikti
module function mean_3_all_${k1}$_dp(x) result(res)
${t1}$, intent(in) :: x(:,:,:)
real(dp) :: res
end function mean_3_all_${k1}$_dp
#:endfor

#:for i1, k1, t1 in iktr
module function mean_3_${k1}$_${k1}$(x, dim) result(res)
${t1}$, intent(in) :: x(:,:,:)
integer, intent(in) :: dim
integer :: j_
${t1}$ :: res( &
merge(size(x,2),size(x,1),mask = any((/(j_, j_ = dim, 3)/) == 1)), &
merge(size(x,3),size(x,2),mask = any((/(j_, j_ = dim, 3)/) == 2)) )
end function mean_3_${k1}$_${k1}$
#:endfor

#:for i1, k1, t1 in ikti
module function mean_3_${k1}$_dp(x, dim) result(res)
${t1}$, intent(in) :: x(:,:,:)
integer, intent(in) :: dim
integer :: j_
real(dp) :: res( &
merge(size(x,2),size(x,1),mask = any((/(j_, j_ = dim, 3)/) == 1)), &
merge(size(x,3),size(x,2),mask = any((/(j_, j_ = dim, 3)/) == 2)) )
end function mean_3_${k1}$_dp
#:endfor

end interface

end module
Loading

0 comments on commit 7612613

Please sign in to comment.