@@ -108,8 +108,8 @@ Pure function.
108108
109109#### Argument
110110
111- - ` array ` : Shall be an array of ` character ` scalar or array of [[ stdlib_string_type(module): string_type (type)]] .
112- This argument is ` intent(in) ` and ` optional ` .
111+ - ` array ` : Shall be an array of ` character ` scalar or array of [[ stdlib_string_type(module): string_type (type)]] .
112+ This argument is ` intent(in) ` and ` optional ` .
113113
114114#### Result value
115115
@@ -353,4 +353,210 @@ program demo_clear
353353 ! stringlist <-- {"Element No. one"}
354354
355355end program demo_clear
356+ ```
357+
358+
359+ <!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
360+ ### Comparison operator equal
361+
362+ #### Description
363+
364+ Compares left hand side (lhs) with right hand side (rhs) for equality.
365+
366+ #### Syntax
367+
368+ ` res = lhs == rhs `
369+
370+ ` res = lhs .eq. rhs `
371+
372+ #### Status
373+
374+ Experimental.
375+
376+ #### Class
377+
378+ Pure function, ` operator(==) ` and ` operator(.eq.) ` .
379+
380+ #### Argument
381+
382+ - ` lhs ` : Shall be an array of ` character ` scalar or of [[ stdlib_string_type(module): string_type (type)]] OR
383+ a [[ stdlib_stringlist_type(module): stringlist_type (type)]] .
384+ This argument is ` intent(in) ` .
385+
386+ - ` rhs ` : Shall be an array of ` character ` scalar or of [[ stdlib_string_type(module): string_type (type)]] OR
387+ a [[ stdlib_stringlist_type(module): stringlist_type (type)]] .
388+ This argument is ` intent(in) ` .
389+
390+ #### Result value
391+
392+ The result is a default logical scalar value.
393+
394+ #### Example
395+
396+ ``` fortran
397+ program demo_equality_operator
398+ use stdlib_stringlist_type, only: stringlist_type, fidx, list_head, operator(==)
399+ use stdlib_string_type, only: string_type
400+ implicit none
401+
402+ type(stringlist_type) :: stringlist
403+ type(string_type), allocatable :: stringarray(:)
404+ logical :: res
405+
406+ !> inserting 4 elements to the stringlist
407+ call stringlist%insert_at( fidx(1), "#1" )
408+ call stringlist%insert_at( list_head, "#2" )
409+ call stringlist%insert_at( fidx(1), "#3" )
410+ call stringlist%insert_at( list_head, "#4" )
411+ ! stringlist <-- {"#4", "#3", "#2", "#1"}
412+
413+ !> creating an array of 4 string_type elements
414+ stringarray = [string_type("#4"), string_type("#3"), string_type("#2"), string_type("#1")]
415+
416+ res = ( stringarray == stringlist )
417+ ! res <-- .true.
418+
419+ res = ( stringlist == ["#4", "#3", "#2", "#1"] )
420+ ! res <-- .true.
421+
422+ print'(a)', stringlist == ["#4", "#3", "#1"]
423+ ! .false.
424+
425+ end program demo_equality_operator
426+ ```
427+
428+
429+ <!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
430+ ### Comparison operator not equal
431+
432+ #### Description
433+
434+ Compares left hand side (lhs) with right hand side (rhs) for inequality.
435+
436+ #### Syntax
437+
438+ ` res = lhs /= rhs `
439+
440+ ` res = lhs .ne. rhs `
441+
442+ #### Status
443+
444+ Experimental.
445+
446+ #### Class
447+
448+ Pure function, ` operator(/=) ` and ` operator(.ne.) ` .
449+
450+ #### Argument
451+
452+ - ` lhs ` : Shall be an array of ` character ` scalar or of [[ stdlib_string_type(module): string_type (type)]] OR
453+ a [[ stdlib_stringlist_type(module): stringlist_type (type)]] .
454+ This argument is ` intent(in) ` .
455+
456+ - ` rhs ` : Shall be an array of ` character ` scalar or of [[ stdlib_string_type(module): string_type (type)]] OR
457+ a [[ stdlib_stringlist_type(module): stringlist_type (type)]] .
458+ This argument is ` intent(in) ` .
459+
460+ #### Result value
461+
462+ The result is a default logical scalar value.
463+
464+ #### Example
465+
466+ ``` fortran
467+ program demo_inequality_operator
468+ use stdlib_stringlist_type, only: stringlist_type, bidx, list_tail, operator(/=)
469+ use stdlib_string_type, only: string_type
470+ implicit none
471+
472+ type(stringlist_type) :: stringlist
473+ type(string_type), allocatable :: stringarray(:)
474+ logical :: res
475+
476+ !> inserting 4 elements to the stringlist
477+ call stringlist%insert_at( bidx(1), "#1" )
478+ call stringlist%insert_at( list_tail, "#2" )
479+ call stringlist%insert_at( bidx(1), "#3" )
480+ call stringlist%insert_at( list_tail, "#4" )
481+ ! stringlist <-- {"#1", "#2", "#3", "#4"}
482+
483+ !> creating an array of 4 string_type elements
484+ stringarray = [string_type("#1"), string_type("#2"), string_type("#3"), string_type("#4")]
485+
486+ res = ( stringarray /= stringlist )
487+ ! res <-- .false.
488+
489+ res = ( stringlist /= ["#111", "#222", "#333", "#444"] )
490+ ! res <-- .true.
491+
492+ print'(a)', stringlist /= ["#4", "#3", "#1"]
493+ ! .true.
494+
495+ end program demo_inequality_operator
496+ ```
497+
498+
499+ <!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
500+ ### Concatenation operator(//)
501+
502+ #### Description
503+
504+ Concatenates left hand side (lhs) and right hand side (rhs).
505+
506+ #### Syntax
507+
508+ ` res = lhs // rhs `
509+
510+ #### Status
511+
512+ Experimental.
513+
514+ #### Class
515+
516+ Pure function, ` operator(//) ` .
517+
518+ #### Argument
519+
520+ - ` lhs ` : Shall be a ` character ` scalar or [[ stdlib_string_type(module): string_type (type)]] OR an array of ` character ` scalar or of [[ stdlib_string_type(module): string_type (type)]] OR
521+ a [[ stdlib_stringlist_type(module): stringlist_type (type)]] .
522+ This argument is ` intent(in) ` .
523+
524+ - ` rhs ` : Shall be a ` character ` scalar or [[ stdlib_string_type(module): string_type (type)]] OR an array of ` character ` scalar or of [[ stdlib_string_type(module): string_type (type)]] OR
525+ a [[ stdlib_stringlist_type(module): stringlist_type (type)]] .
526+ This argument is ` intent(in) ` .
527+
528+ #### Result value
529+
530+ The result is an instance of ` stringlist_type ` .
531+
532+ #### Example
533+
534+ ``` fortran
535+ program demo_concatenate_operator
536+ use stdlib_stringlist_type, only: stringlist_type, operator(//)
537+ use stdlib_string_type, only: string_type
538+ implicit none
539+
540+ type(stringlist_type) :: first_stringlist, second_stringlist
541+ type(string_type), allocatable :: stringarray(:)
542+
543+ first_stringlist = first_stringlist // "Element No. one"
544+ ! first_stringlist <-- {"Element No. one"}
545+
546+ second_stringlist = string_type("Element No. two") // first_stringlist
547+ ! second_stringlist <-- {Element No. two, "Element No. one"}
548+
549+ !> Creating an array of 2 string_type elements
550+ stringarray = [string_type("Element No. three"), string_type("Element No. four")]
551+
552+ second_stringlist = first_stringlist // stringarray
553+ ! second_stringlist <-- {"Element No. one", "Element No. three", "Element No. four"}
554+
555+ second_stringlist = ["#1", "#2"] // second_stringlist
556+ ! second_stringlist <-- {"#1", "#2", "Element No. one", "Element No. three", "Element No. four"}
557+
558+ first_stringlist = first_stringlist // second_stringlist
559+ ! first_stringlist <-- {"Element No. one", "#1", "#2", "Element No. one", "Element No. three", "Element No. four"}
560+
561+ end program demo_concatenate_operator
356562```
0 commit comments