Skip to content

Commit

Permalink
Merge branch 'fortran-lang:master' into ascii_elemental
Browse files Browse the repository at this point in the history
  • Loading branch information
jalvesz authored Nov 25, 2024
2 parents fd2396c + 68524b3 commit 882966e
Show file tree
Hide file tree
Showing 2 changed files with 14 additions and 13 deletions.
4 changes: 2 additions & 2 deletions doc/specs/stdlib_stats_distribution_normal.md
Original file line number Diff line number Diff line change
Expand Up @@ -64,11 +64,11 @@ Experimental

The probability density function (pdf) of the single real variable normal distribution:

$$f(x) = \frac{1}{\sigma \sqrt{2}} \exp{\left[-\frac{1}{2}\left(\frac{x-\mu}{\sigma}\right)^{2}\right]}$$
$$f(x) = \frac{1}{\sigma \sqrt{2\pi}} \exp{\left[-\frac{1}{2}\left(\frac{x-\mu}{\sigma}\right)^{2}\right]}$$

For a complex varible \( z=(x + y i) \) with independent real \( x \) and imaginary \( y \) parts, the joint probability density function is the product of the the corresponding real and imaginary marginal pdfs:[^2]

$$f(x + y \mathit{i}) = f(x) f(y) = \frac{1}{2\sigma_{x}\sigma_{y}} \exp{\left[-\frac{1}{2}\left(\left(\frac{x-\mu_x}{\sigma_{x}}\right)^{2}+\left(\frac{y-\mu_y}{\sigma_{y}}\right)^{2}\right)\right]}$$
$$f(x + y \mathit{i}) = f(x) f(y) = \frac{1}{2\pi\sigma_{x}\sigma_{y}} \exp{\left[-\frac{1}{2}\left(\left(\frac{x-\mu_x}{\sigma_{x}}\right)^{2}+\left(\frac{y-\mu_y}{\sigma_{y}}\right)^{2}\right)\right]}$$

### Syntax

Expand Down
23 changes: 12 additions & 11 deletions src/stdlib_io.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ module stdlib_io
use, intrinsic :: iso_fortran_env, only : input_unit
use stdlib_kinds, only: sp, dp, xdp, qp, &
int8, int16, int32, int64
use stdlib_error, only: error_stop
use stdlib_optval, only: optval
use stdlib_ascii, only: is_blank
use stdlib_string_type, only : string_type
Expand Down Expand Up @@ -120,7 +121,7 @@ contains
!!
integer :: s
integer :: nrow, ncol, i, ios, skiprows_, max_rows_
character(len=128) :: iomsg, msgout
character(len=1024) :: iomsg, msgout

skiprows_ = max(optval(skiprows, 0), 0)
max_rows_ = optval(max_rows, -1)
Expand All @@ -146,7 +147,7 @@ contains

if (ios/=0) then
write(msgout,1) trim(iomsg),i,trim(filename)
error stop trim(msgout)
call error_stop(msg=trim(msgout))
end if

end do
Expand All @@ -167,7 +168,7 @@ contains

if (ios/=0) then
write(msgout,1) trim(iomsg),i,trim(filename)
error stop trim(msgout)
call error_stop(msg=trim(msgout))
end if

enddo
Expand All @@ -178,7 +179,7 @@ contains

if (ios/=0) then
write(msgout,1) trim(iomsg),i,trim(filename)
error stop trim(msgout)
call error_stop(msg=trim(msgout))
end if

enddo
Expand Down Expand Up @@ -214,7 +215,7 @@ contains
!!

integer :: s, i, ios
character(len=128) :: iomsg, msgout
character(len=1024) :: iomsg, msgout
s = open(filename, "w")
do i = 1, size(d, 1)
#:if 'real' in t1
Expand All @@ -230,7 +231,7 @@ contains

if (ios/=0) then
write(msgout,1) trim(iomsg),i,trim(filename)
error stop trim(msgout)
call error_stop(msg=trim(msgout))
end if

end do
Expand Down Expand Up @@ -366,7 +367,7 @@ contains
position_='asis'
status_='new'
case default
error stop "Unsupported mode: "//mode_(1:2)
call error_stop("Unsupported mode: "//mode_(1:2))
end select

select case (mode_(3:3))
Expand All @@ -375,7 +376,7 @@ contains
case('b')
form_='unformatted'
case default
error stop "Unsupported mode: "//mode_(3:3)
call error_stop("Unsupported mode: "//mode_(3:3))
end select

access_ = 'stream'
Expand Down Expand Up @@ -421,9 +422,9 @@ contains
else if (a(i:i) == ' ') then
cycle
else if(any(.not.lfirst)) then
error stop "Wrong mode: "//trim(a)
call error_stop("Wrong mode: "//trim(a))
else
error stop "Wrong character: "//a(i:i)
call error_stop("Wrong character: "//a(i:i))
endif
end do

Expand Down Expand Up @@ -472,7 +473,7 @@ contains
if (present(iostat)) then
iostat = stat
else if (stat /= 0) then
error stop trim(msg)
call error_stop(trim(msg))
end if
end subroutine getline_char

Expand Down

0 comments on commit 882966e

Please sign in to comment.