@@ -184,8 +184,370 @@ All the ascii whitespace characters (space, horizontal tab, vertical tab, carria
184184
185185## Specification of the ` stdlib_ascii ` procedures
186186
187- @ note Specification of procedures is currently incomplete.
187+ ### ` is_alpha `
188188
189+ #### Status
190+
191+ Experimental
192+
193+ #### Description
194+
195+ Checks whether input character is an ASCII letter (A-Z, a-z).
196+
197+ #### Syntax
198+
199+ ` res = ` [[ stdlib_ascii(module): is_alpha (function)]] ` (c) `
200+
201+ #### Class
202+
203+ Elemental function.
204+
205+ #### Argument
206+
207+ ` c ` : shall be an intrinsic ` character(len=1) ` type. It is an ` intent(in) ` argument.
208+
209+ #### Result value
210+
211+ The result is a ` logical ` .
212+
213+ ### ` is_alphanum `
214+
215+ #### Status
216+
217+ Experimental
218+
219+ #### Description
220+
221+ Checks whether input character is an ASCII letter or a number (A-Z, a-z, 0-9).
222+
223+ #### Syntax
224+
225+ ` res = ` [[ stdlib_ascii(module): is_alphanum (function)]] ` (c) `
226+
227+ #### Class
228+
229+ Elemental function.
230+
231+ #### Argument
232+
233+ ` c ` : shall be an intrinsic ` character(len=1) ` type. It is an ` intent(in) ` argument.
234+
235+ #### Result value
236+
237+ The result is a ` logical ` .
238+
239+ ### ` is_ascii `
240+
241+ #### Status
242+
243+ Experimental
244+
245+ #### Description
246+
247+ Checks whether input character is in the ASCII character set i.e in the range 0-128.
248+
249+ #### Syntax
250+
251+ ` res = ` [[ stdlib_ascii(module): is_ascii (function)]] ` (c) `
252+
253+ #### Class
254+
255+ Elemental function.
256+
257+ #### Argument
258+
259+ ` c ` : shall be an intrinsic ` character(len=1) ` type. It is an ` intent(in) ` argument.
260+
261+ #### Result value
262+
263+ The result is a ` logical ` .
264+
265+ ### ` is_control `
266+
267+ #### Status
268+
269+ Experimental
270+
271+ #### Description
272+
273+ Checks whether input character is a control character.
274+
275+ #### Syntax
276+
277+ ` res = ` [[ stdlib_ascii(module): is_control (function)]] ` (c) `
278+
279+ #### Class
280+
281+ Elemental function.
282+
283+ #### Argument
284+
285+ ` c ` : shall be an intrinsic ` character(len=1) ` type. It is an ` intent(in) ` argument.
286+
287+ #### Result value
288+
289+ The result is a ` logical ` .
290+
291+ ### ` is_digit `
292+
293+ #### Status
294+
295+ Experimental
296+
297+ #### Description
298+
299+ Checks whether input character is a digit (0-9).
300+
301+ #### Syntax
302+
303+ ` res = ` [[ stdlib_ascii(module): is_digit (function)]] ` (c) `
304+
305+ #### Class
306+
307+ Elemental function.
308+
309+ #### Argument
310+
311+ ` c ` : shall be an intrinsic ` character(len=1) ` type. It is an ` intent(in) ` argument.
312+
313+ #### Result value
314+
315+ The result is a ` logical ` .
316+
317+ ### ` is_octal_digit `
318+
319+ #### Status
320+
321+ Experimental
322+
323+ #### Description
324+
325+ Checks whether input character is an octal digit (0-7)
326+
327+ #### Syntax
328+
329+ ` res = ` [[ stdlib_ascii(module): is_octal_digit (function)]] ` (c) `
330+
331+ #### Class
332+
333+ Elemental function.
334+
335+ #### Argument
336+
337+ ` c ` : shall be an intrinsic ` character(len=1) ` type. It is an ` intent(in) ` argument.
338+
339+ #### Result value
340+
341+ The result is a ` logical ` .
342+
343+ ### ` is_hex_digit `
344+
345+ #### Status
346+
347+ Experimental
348+
349+ #### Description
350+
351+ Checks whether input character is a hexadecimal digit (0-9, A-F, a-f).
352+
353+ #### Syntax
354+
355+ ` res = ` [[ stdlib_ascii(module): is_hex_digit (function)]] ` (c) `
356+
357+ #### Class
358+
359+ Elemental function.
360+
361+ #### Argument
362+
363+ ` c ` : shall be an intrinsic ` character(len=1) ` type. It is an ` intent(in) ` argument.
364+
365+ #### Result value
366+
367+ The result is a ` logical ` .
368+
369+ ### ` is_punctuation `
370+
371+ #### Status
372+
373+ Experimental
374+
375+ #### Description
376+
377+ Checks whether input character is a punctuation character.
378+
379+ #### Syntax
380+
381+ ` res = ` [[ stdlib_ascii(module): is_punctuation (function)]] ` (c) `
382+
383+ #### Class
384+
385+ Elemental function.
386+
387+ #### Argument
388+
389+ ` c ` : shall be an intrinsic ` character(len=1) ` type. It is an ` intent(in) ` argument.
390+
391+ #### Result value
392+
393+ The result is a ` logical ` .
394+
395+ ### ` is_graphical `
396+
397+ #### Status
398+
399+ Experimental
400+
401+ #### Description
402+
403+ Checks whether input character is a graphical character (printable other than the space character).
404+
405+ #### Syntax
406+
407+ ` res = ` [[ stdlib_ascii(module): is_graphical (function)]] ` (c) `
408+
409+ #### Class
410+
411+ Elemental function.
412+
413+ #### Argument
414+
415+ ` c ` : shall be an intrinsic ` character(len=1) ` type. It is an ` intent(in) ` argument.
416+
417+ #### Result value
418+
419+ The result is a ` logical ` .
420+
421+ ### ` is_printable `
422+
423+ #### Status
424+
425+ Experimental
426+
427+ #### Description
428+
429+ Checks whether input character is a printable character (including the space character).
430+
431+ #### Syntax
432+
433+ ` res = ` [[ stdlib_ascii(module): is_printable (function)]] ` (c) `
434+
435+ #### Class
436+
437+ Elemental function.
438+
439+ #### Argument
440+
441+ ` c ` : shall be an intrinsic ` character(len=1) ` type. It is an ` intent(in) ` argument.
442+
443+ #### Result value
444+
445+ The result is a ` logical ` .
446+
447+ ### ` is_lower `
448+
449+ #### Status
450+
451+ Experimental
452+
453+ #### Description
454+
455+ Checks whether input character is a lowercase ASCII letter (a-z).
456+
457+ #### Syntax
458+
459+ ` res = ` [[ stdlib_ascii(module): is_lower (function)]] ` (c) `
460+
461+ #### Class
462+
463+ Elemental function.
464+
465+ #### Argument
466+
467+ ` c ` : shall be an intrinsic ` character(len=1) ` type. It is an ` intent(in) ` argument.
468+
469+ #### Result value
470+
471+ The result is a ` logical ` .
472+
473+ ### ` is_upper `
474+
475+ #### Status
476+
477+ Experimental
478+
479+ #### Description
480+
481+ Checks whether input character is an uppercase ASCII letter (A-Z).
482+
483+ #### Syntax
484+
485+ ` res = ` [[ stdlib_ascii(module): is_upper (function)]] ` (c) `
486+
487+ #### Class
488+
489+ Elemental function.
490+
491+ #### Argument
492+
493+ ` c ` : shall be an intrinsic ` character(len=1) ` type. It is an ` intent(in) ` argument.
494+
495+ #### Result value
496+
497+ The result is a ` logical ` .
498+
499+ ### ` is_white `
500+
501+ #### Status
502+
503+ Experimental
504+
505+ #### Description
506+
507+ Checks whether input character is a whitespace character (which includes space, horizontal tab, vertical tab,
508+ carriage return, linefeed and form feed characters)
509+
510+ #### Syntax
511+
512+ ` res = ` [[ stdlib_ascii(module): is_white (function)]] ` (c) `
513+
514+ #### Class
515+
516+ Elemental function.
517+
518+ #### Argument
519+
520+ ` c ` : shall be an intrinsic ` character(len=1) ` type. It is an ` intent(in) ` argument.
521+
522+ #### Result value
523+
524+ The result is a ` logical ` .
525+
526+ ### ` is_blank `
527+
528+ #### Status
529+
530+ Experimental
531+
532+ #### Description
533+
534+ Checks whether input character is a blank character (which includes space and tabs).
535+
536+ #### Syntax
537+
538+ ` res = ` [[ stdlib_ascii(module): is_blank (function)]] ` (c) `
539+
540+ #### Class
541+
542+ Elemental function.
543+
544+ #### Argument
545+
546+ ` c ` : shall be an intrinsic ` character(len=1) ` type. It is an ` intent(in) ` argument.
547+
548+ #### Result value
549+
550+ The result is a ` logical ` .
189551
190552### ` to_lower `
191553
@@ -217,7 +579,7 @@ The result is an intrinsic character type of the same length as `string`.
217579
218580``` fortran
219581{!example/ascii/example_ascii_to_lower.f90!}
220- ```
582+ ```
221583
222584### ` to_upper `
223585
0 commit comments