@@ -6,17 +6,17 @@ module stdlib_linalg_state
66 !! Provides a state/error handling derived type for advanced error handling of
77 !! BLAS/LAPACK based linear algebra procedures. All procedures are pure.
88 !! !! ([Specification](../page/specs/stdlib_linalg.html))
9- use stdlib_linalg_constants,only:ilp,lk
10- use stdlib_kinds
11- use stdlib_io
12- use iso_fortran_env,only: stderr => error_unit
9+ use stdlib_linalg_constants,only: ilp,sp,dp,qp ,lk
10+ use stdlib_kinds, only: int8, int16, int32, int64
11+ use stdlib_io, only: FMT_REAL_SP, FMT_REAL_DP, FMT_REAL_QP, FMT_COMPLEX_SP, FMT_COMPLEX_DP, &
12+ FMT_COMPLEX_QP
1313 implicit none(type,external)
1414 private
1515
1616 !> Version: experimental
1717 !>
1818 !> A fixed-storage state variable for error handling of linear algebra routines
19- public :: linalg_state
19+ public :: linalg_state_type
2020
2121 !> Version: experimental
2222 !>
@@ -32,19 +32,19 @@ module stdlib_linalg_state
3232 public :: operator(>),operator(>=)
3333
3434 !> State return types
35- integer(ilp),parameter,public :: LINALG_SUCCESS = 0_ilp
36- integer(ilp),parameter,public :: LINALG_VALUE_ERROR = -1_ilp
37- integer(ilp),parameter,public :: LINALG_ERROR = -2_ilp
35+ integer(ilp),parameter,public :: LINALG_SUCCESS = 0_ilp
36+ integer(ilp),parameter,public :: LINALG_VALUE_ERROR = -1_ilp
37+ integer(ilp),parameter,public :: LINALG_ERROR = -2_ilp
3838 integer(ilp),parameter,public :: LINALG_INTERNAL_ERROR = -3_ilp
3939
4040 !> Use fixed-size character storage for performance
4141 integer(ilp),parameter :: MSG_LENGTH = 512_ilp
4242 integer(ilp),parameter :: NAME_LENGTH = 32_ilp
4343
44- !> `linalg_state ` defines a state return type for a
44+ !> `linalg_state_type ` defines a state return type for a
4545 !> linear algebra routine. State contains a status flag, a comment, and a
4646 !> procedure specifier that can be used to mark where the error happened
47- type :: linalg_state
47+ type :: linalg_state_type
4848
4949 !> The current exit state
5050 integer(ilp) :: state = LINALG_SUCCESS
@@ -58,17 +58,17 @@ module stdlib_linalg_state
5858 contains
5959
6060 !> Cleanup
61- procedure :: destroy => state_destroy
61+ procedure :: destroy => state_destroy
6262
6363 !> Print error message
64- procedure :: print => state_print
64+ procedure :: print => state_print
6565 procedure :: print_msg => state_message
6666
6767 !> State properties
68- procedure :: ok => state_is_ok
69- procedure :: error => state_is_error
68+ procedure :: ok => state_is_ok
69+ procedure :: error => state_is_error
7070
71- end type linalg_state
71+ end type linalg_state_type
7272
7373 !> Comparison operators
7474 interface operator(==)
@@ -96,15 +96,15 @@ module stdlib_linalg_state
9696 module procedure flag_ge_state
9797 end interface
9898
99- interface linalg_state
99+ interface linalg_state_type
100100 module procedure new_state
101101 module procedure new_state_nowhere
102- end interface linalg_state
102+ end interface linalg_state_type
103103
104104 contains
105105
106106 !> Interface to print linalg state flags
107- pure function LINALG_MESSAGE (flag) result(msg)
107+ pure function linalg_message (flag) result(msg)
108108 integer(ilp),intent(in) :: flag
109109 character(len=:),allocatable :: msg
110110
@@ -116,12 +116,12 @@ module stdlib_linalg_state
116116 case default; msg = 'ERROR/INVALID FLAG'
117117 end select
118118
119- end function LINALG_MESSAGE
119+ end function linalg_message
120120
121121 !> Flow control: on output flag present, return it; otherwise, halt on error
122122 pure subroutine linalg_error_handling(ierr,ierr_out)
123- type(linalg_state ),intent(in) :: ierr
124- type(linalg_state ),optional,intent(out) :: ierr_out
123+ type(linalg_state_type ),intent(in) :: ierr
124+ type(linalg_state_type ),optional,intent(out) :: ierr_out
125125
126126 character(len=:),allocatable :: err_msg
127127
@@ -137,20 +137,20 @@ module stdlib_linalg_state
137137
138138 !> Formatted message
139139 pure function state_message(this) result(msg)
140- class(linalg_state ),intent(in) :: this
140+ class(linalg_state_type ),intent(in) :: this
141141 character(len=:),allocatable :: msg
142142
143143 if (this%state == LINALG_SUCCESS) then
144144 msg = 'Success!'
145145 else
146- msg = LINALG_MESSAGE (this%state)//': '//trim(this%message)
146+ msg = linalg_message (this%state)//': '//trim(this%message)
147147 end if
148148
149149 end function state_message
150150
151151 !> Produce a nice error string
152152 pure function state_print(this) result(msg)
153- class(linalg_state ),intent(in) :: this
153+ class(linalg_state_type ),intent(in) :: this
154154 character(len=:),allocatable :: msg
155155
156156 if (len_trim(this%where_at) > 0) then
@@ -165,7 +165,7 @@ module stdlib_linalg_state
165165
166166 !> Cleanup the object
167167 elemental subroutine state_destroy(this)
168- class(linalg_state ),intent(inout) :: this
168+ class(linalg_state_type ),intent(inout) :: this
169169
170170 this%state = LINALG_SUCCESS
171171 this%message = repeat(' ',len(this%message))
@@ -175,102 +175,102 @@ module stdlib_linalg_state
175175
176176 !> Check if the current state is successful
177177 elemental logical(lk) function state_is_ok(this)
178- class(linalg_state ),intent(in) :: this
178+ class(linalg_state_type ),intent(in) :: this
179179 state_is_ok = this%state == LINALG_SUCCESS
180180 end function state_is_ok
181181
182182 !> Check if the current state is an error state
183183 elemental logical(lk) function state_is_error(this)
184- class(linalg_state ),intent(in) :: this
184+ class(linalg_state_type ),intent(in) :: this
185185 state_is_error = this%state /= LINALG_SUCCESS
186186 end function state_is_error
187187
188188 !> Compare an error state with an integer flag
189189 elemental logical(lk) function state_eq_flag(err,flag)
190- type(linalg_state ),intent(in) :: err
190+ type(linalg_state_type ),intent(in) :: err
191191 integer,intent(in) :: flag
192192 state_eq_flag = err%state == flag
193193 end function state_eq_flag
194194
195195 !> Compare an integer flag with the error state
196196 elemental logical(lk) function flag_eq_state(flag,err)
197197 integer,intent(in) :: flag
198- type(linalg_state ),intent(in) :: err
198+ type(linalg_state_type ),intent(in) :: err
199199 flag_eq_state = err%state == flag
200200 end function flag_eq_state
201201
202202 !> Compare the error state with an integer flag
203203 elemental logical(lk) function state_neq_flag(err,flag)
204- type(linalg_state ),intent(in) :: err
204+ type(linalg_state_type ),intent(in) :: err
205205 integer,intent(in) :: flag
206206 state_neq_flag = .not. state_eq_flag(err,flag)
207207 end function state_neq_flag
208208
209209 !> Compare an integer flag with the error state
210210 elemental logical(lk) function flag_neq_state(flag,err)
211211 integer,intent(in) :: flag
212- type(linalg_state ),intent(in) :: err
212+ type(linalg_state_type ),intent(in) :: err
213213 flag_neq_state = .not. state_eq_flag(err,flag)
214214 end function flag_neq_state
215215
216216 !> Compare the error state with an integer flag
217217 elemental logical(lk) function state_lt_flag(err,flag)
218- type(linalg_state ),intent(in) :: err
218+ type(linalg_state_type ),intent(in) :: err
219219 integer,intent(in) :: flag
220220 state_lt_flag = err%state < flag
221221 end function state_lt_flag
222222
223223 !> Compare the error state with an integer flag
224224 elemental logical(lk) function state_le_flag(err,flag)
225- type(linalg_state ),intent(in) :: err
225+ type(linalg_state_type ),intent(in) :: err
226226 integer,intent(in) :: flag
227227 state_le_flag = err%state <= flag
228228 end function state_le_flag
229229
230230 !> Compare an integer flag with the error state
231231 elemental logical(lk) function flag_lt_state(flag,err)
232232 integer,intent(in) :: flag
233- type(linalg_state ),intent(in) :: err
233+ type(linalg_state_type ),intent(in) :: err
234234 flag_lt_state = err%state < flag
235235 end function flag_lt_state
236236
237237 !> Compare an integer flag with the error state
238238 elemental logical(lk) function flag_le_state(flag,err)
239239 integer,intent(in) :: flag
240- type(linalg_state ),intent(in) :: err
240+ type(linalg_state_type ),intent(in) :: err
241241 flag_le_state = err%state <= flag
242242 end function flag_le_state
243243
244244 !> Compare the error state with an integer flag
245245 elemental logical(lk) function state_gt_flag(err,flag)
246- type(linalg_state ),intent(in) :: err
246+ type(linalg_state_type ),intent(in) :: err
247247 integer,intent(in) :: flag
248248 state_gt_flag = err%state > flag
249249 end function state_gt_flag
250250
251251 !> Compare the error state with an integer flag
252252 elemental logical(lk) function state_ge_flag(err,flag)
253- type(linalg_state ),intent(in) :: err
253+ type(linalg_state_type ),intent(in) :: err
254254 integer,intent(in) :: flag
255255 state_ge_flag = err%state >= flag
256256 end function state_ge_flag
257257
258258 !> Compare an integer flag with the error state
259259 elemental logical(lk) function flag_gt_state(flag,err)
260260 integer,intent(in) :: flag
261- type(linalg_state ),intent(in) :: err
261+ type(linalg_state_type ),intent(in) :: err
262262 flag_gt_state = err%state > flag
263263 end function flag_gt_state
264264
265265 !> Compare an integer flag with the error state
266266 elemental logical(lk) function flag_ge_state(flag,err)
267267 integer,intent(in) :: flag
268- type(linalg_state ),intent(in) :: err
268+ type(linalg_state_type ),intent(in) :: err
269269 flag_ge_state = err%state >= flag
270270 end function flag_ge_state
271271
272272 !> Error creation message, with location location
273- pure type(linalg_state ) function new_state(where_at,flag,a1,a2,a3,a4,a5,a6,a7,a8,a9,a10, &
273+ pure type(linalg_state_type ) function new_state(where_at,flag,a1,a2,a3,a4,a5,a6,a7,a8,a9,a10, &
274274 v1,v2,v3,v4,v5)
275275
276276 !> Location
@@ -294,7 +294,7 @@ module stdlib_linalg_state
294294 end function new_state
295295
296296 !> Error creation message, from N input variables (numeric or strings)
297- pure type(linalg_state ) function new_state_nowhere(flag,a1,a2,a3,a4,a5,a6,a7,a8,a9,a10, &
297+ pure type(linalg_state_type ) function new_state_nowhere(flag,a1,a2,a3,a4,a5,a6,a7,a8,a9,a10, &
298298 v1,v2,v3,v4,v5) result(new_state)
299299
300300 !> Input error flag
0 commit comments