diff --git a/doc/specs/stdlib_stats_distribution_normal.md b/doc/specs/stdlib_stats_distribution_normal.md index db32a3b60..7217171e3 100644 --- a/doc/specs/stdlib_stats_distribution_normal.md +++ b/doc/specs/stdlib_stats_distribution_normal.md @@ -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 diff --git a/src/stdlib_io.fypp b/src/stdlib_io.fypp index ac207a944..556d0281f 100644 --- a/src/stdlib_io.fypp +++ b/src/stdlib_io.fypp @@ -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 @@ -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) @@ -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 @@ -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 @@ -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 @@ -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 @@ -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 @@ -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)) @@ -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' @@ -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 @@ -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