Optional parameters

From Rosetta Code
Task
Optional parameters
You are encouraged to solve this task according to the task description, using any language you may know.

Define a function/method/subroutine which sorts a sequence ("table") of sequences ("rows") of strings ("cells"), by one of the strings. Besides the input to be sorted, it shall have the following optional parameters:

ordering
A function specifying the ordering of strings; lexicographic by default.
column
An integer specifying which string of each row to compare; the first by default.
reverse
Reverses the ordering.

This task should be considered to include both positional and named optional parameters, as well as overloading on argument count as in Java or selector name as in Smalltalk, or, in the extreme, using different function names. Provide these variations of sorting in whatever way is most natural to your language.

Do not implement a sorting algorithm; this task is about the interface. If you can't use a built-in sort routine, just omit the implementation (with a comment).

Common Lisp

Common Lisp has both named and positional parameters.

<lang lisp> (defun sort-table (table &key (ordering #'string<)

                             (column 0)
                             reverse)
 (sort table (if reverse
                 (complement ordering)
                 ordering)
             :key (lambda (row) (elt row column))))</lang>

(Notes: The builtin sort takes a "less than" predicate function. The complement function inverts a predicate.)

Example uses: <lang lisp>CL-USER> (defparameter *data* '(("a" "b" "c") ("" "q" "z") ("zap" "zip" "Zot")))

  • DATA*

CL-USER> (sort-table *data*) (("" "q" "z") ("a" "b" "c") ("zap" "zip" "Zot"))

CL-USER> (sort-table *data* :column 2) (("zap" "zip" "Zot") ("a" "b" "c") ("" "q" "z"))

CL-USER> (sort-table *data* :column 1) (("a" "b" "c") ("" "q" "z") ("zap" "zip" "Zot"))

CL-USER> (sort-table *data* :column 1 :reverse t) (("zap" "zip" "Zot") ("" "q" "z") ("a" "b" "c"))

CL-USER> (sort-table *data* :ordering (lambda (a b) (> (length a) (length b)))) (("zap" "zip" "Zot") ("a" "b" "c") ("" "q" "z"))</lang>

Fortran

Works with: Fortran version 95 and later

In Fortran, each argument has its "name". The optional attribute can be used to specify that an argument is optional, and its presence (or absence) can be tested using the present intrinsic (so that we can give a default value, or execute accordingly a totally different code).

<lang fortran>module ExampleOptionalParameter

 ! use any module needed for the sort function(s)
 ! and all the interfaces needed to make the code work
 implicit none

contains

 subroutine sort_table(table, ordering, column, reverse)
   type(table_type), intent(inout) :: table
   integer, optional :: column
   logical, optional :: reverse
   optional :: ordering
   interface
      integer function ordering(a, b)
        type(table_element), intent(in) :: a, b
      end function ordering
   end interface
   integer :: the_column, i
   logical :: reversing
   type(table_row) :: rowA, rowB
   if ( present(column) ) then
      if ( column > get_num_of_columns(table) ) then
         ! raise an error?
      else
         the_column = column
      end if
   else
      the_column = 1   ! a default value, de facto
   end if
   reversing = .false.  ! default value
   if ( present(reverse) ) reversing = reverse
   do
      ! loops over the rows to sort... at some point, we need
      ! comparing an element (cell) of the row, with the element
      ! in another row; ... let us suppose rowA and rowB are
      ! the two rows we are considering
      ea = get_element(rowA, the_column)
      eb = get_element(rowB, the_column)
      if ( present(ordering) ) then
         if ( .not. reversing ) then
            if ( ordering(ea, eb) > 0 ) then
               ! swap the rowA with the rowB
            end if
         else   ! < instead of >
            if ( ordering(ea, eb) < 0 ) then
               ! swap the rowA with the rowB
            end if
         end if
      else
         if ( .not. reversing ) then
            if ( lexinternal(ea, eb) > 0 ) then
               ! swap the rowA with the rowB
            end if
         else   ! < instead of >
            if ( lexinternal(ea, eb) < 0 ) then
               ! swap the rowA with the rowB
            end if
         end if
      end if
      ! ... more of the sorting algo ...
      ! ... and rows traversing ... (and an exit condition of course!)
   end do
 end subroutine sort_table

end module ExampleOptionalParameter</lang>

<lang fortran>program UsingTest

 use ExampleOptionalParameter
 implicit none
 type(table_type) :: table
 ! create the table...
 ! sorting taking from column 1, not reversed, using internal
 ! default comparator
 call sort_table(table)
 ! the same as above, but in reversed order; we MUST specify
 ! the name of the argument since it is not given in the same
 ! order of the subroutine spec
 call sort_table(table, reverse=.true.)
 ! sort the table using a custom comparator
 call sort_table(table, my_cmp)
 ! or
 call sort_table(table, ordering=my_cmp)
 ! as above, but taking from column 2
 call sort_table(table, my_cmp, 2)
 ! or (swapping the order of args for fun)
 call sort_table(table, column=2, ordering=my_cmp)
 ! with custom comparator, column 2 and reversing...
 call sort_table(table, my_cmp, 2, .true.)
 ! of course we can swap the order of optional args
 ! by prefixing them with the name of the arg
 ! sort from column 2, with internal comparator
 call sort_table(table, column=2)

end program UsingTest</lang>

Java

Java has no optional parameters, but methods can be overloaded on the number and types of arguments, which can be used to effectively achieve optional positional parameters.

<lang java>import java.util.*;

// the "natural ordering" comparator // taken from Apache Commons Collections class ComparableComparator<T extends Comparable<? super T>>

   implements Comparator<T> {
   public int compare(T a, T b) {
       return a.compareTo(b);
   }

}

public class OptionalParams {

   public static <T extends Comparable<? super T>> void
                            sortTable(T[][] table) {
       sortTable(table, 0);
   }
   public static <T extends Comparable<? super T>> void
                            sortTable(T[][] table,
                                      int column) {
       sortTable(table, column, false);
   }
   public static <T extends Comparable<? super T>> void
                            sortTable(T[][] table,
                                      int column, boolean reverse) {
       sortTable(table, column, reverse, new ComparableComparator<T>());
   }
   public static <T> void sortTable(T[][] table,
                                    final int column,
                                    final boolean reverse,
                                    final Comparator<T> ordering) {
       Comparator<T[]> myCmp = new Comparator<T[]>() {
           public int compare(T[] x, T[] y) {
               return (reverse ? -1 : 1) *
                      ordering.compare(x[column], y[column]);
           }
       };
       Arrays.sort(table, myCmp);
   }
   public static void main(String[] args) {
       String[][] data0 = {{"a", "b", "c"},
                           {"", "q", "z"},
                           {"zap", "zip", "Zot"}};
       System.out.println(Arrays.deepToString(data0));
       // prints: [[a, b, c], [, q, z], [zap, zip, Zot]]
       // we copy it so that we don't change the original copy
       String[][] data = data0.clone();
       sortTable(data);
       System.out.println(Arrays.deepToString(data));
       // prints: [[, q, z], [a, b, c], [zap, zip, Zot]]
       data = data0.clone();
       sortTable(data, 2);
       System.out.println(Arrays.deepToString(data));
       // prints: [[zap, zip, Zot], [a, b, c], [, q, z]]
       data = data0.clone();
       sortTable(data, 1);
       System.out.println(Arrays.deepToString(data));
       // prints: [[a, b, c], [, q, z], [zap, zip, Zot]]
       data = data0.clone();
       sortTable(data, 1, true);
       System.out.println(Arrays.deepToString(data));
       // prints: [[zap, zip, Zot], [, q, z], [a, b, c]]
       data = data0.clone();
       sortTable(data, 0, false, new Comparator<String>() {
               public int compare(String a, String b) {
                   return b.length() - a.length();
               }
           });
       System.out.println(Arrays.deepToString(data));
       // prints: [[zap, zip, Zot], [a, b, c], [, q, z]]
   }

}</lang>

OCaml

OCaml has optional named parameters. It is conventional to place a non-optional parameter after the optional parameters, because if the optional parameters were at the end, then if you don't provide them, it will just look like a partial application (because OCaml supports currying), resulting in a function which still expects the optional parameters.

<lang ocaml>let sort_table ?(ordering = compare) ?(column = 0) ?(reverse = false) table =

 let cmp x y = ordering (List.nth x column) (List.nth y column) * (if reverse then -1 else 1) in
   List.sort cmp table</lang>

Example uses: <lang ocaml># let data = [["a"; "b"; "c"]; [""; "q"; "z"]; ["zap"; "zip"; "Zot"]];; val data : string list list =

 [["a"; "b"; "c"]; [""; "q"; "z"]; ["zap"; "zip"; "Zot"]]
  1. sort_table data;;

- : string list list = [[""; "q"; "z"]; ["a"; "b"; "c"]; ["zap"; "zip"; "Zot"]]

  1. sort_table ~column:2 data;;

- : string list list = [["zap"; "zip"; "Zot"]; ["a"; "b"; "c"]; [""; "q"; "z"]]

  1. sort_table ~column:1 data;;

- : string list list = [["a"; "b"; "c"]; [""; "q"; "z"]; ["zap"; "zip"; "Zot"]]

  1. sort_table ~column:1 ~reverse:true data;;

- : string list list = [["zap"; "zip"; "Zot"]; [""; "q"; "z"]; ["a"; "b"; "c"]]

  1. sort_table ~ordering:(fun a b -> compare (String.length b) (String.length a)) data;;

- : string list list = [["zap"; "zip"; "Zot"]; ["a"; "b"; "c"]; [""; "q"; "z"]]</lang>

OCaml does not support optional positional parameters, because, since OCaml supports currying, it would conflict with partial applications, where you do not provide all the arguments to a function, and it results in a function which expects the remaining arguments.

Python

Works with: Python version 2.x

only (the "cmp" argument to sorted() is no longer accepted in Python 3)

Using a pretty-printer for the table <lang python>>>> def printtable(data):

   for row in data:
       print ' '.join('%-5s' % ('"%s"' % cell) for cell in row)


>>> def sorttable(table, ordering=None, column=0, reverse=False):

   return sorted(table, cmp=ordering, key=lambda row: row[column], reverse=reverse)

>>> data = [["a", "b", "c"], ["", "q", "z"], ["zap", "zip", "Zot"]] >>> printtable(data) "a" "b" "c" "" "q" "z" "zap" "zip" "Zot" >>> printtable( sorttable(data) ) "" "q" "z" "a" "b" "c" "zap" "zip" "Zot" >>> printtable( sorttable(data, column=2) ) "zap" "zip" "Zot" "a" "b" "c" "" "q" "z" >>> printtable( sorttable(data, column=1) ) "a" "b" "c" "" "q" "z" "zap" "zip" "Zot" >>> printtable( sorttable(data, column=1, reverse=True) ) "zap" "zip" "Zot" "" "q" "z" "a" "b" "c" >>> printtable( sorttable(data, ordering=lambda a,b: cmp(len(b),len(a))) ) "zap" "zip" "Zot" "a" "b" "c" "" "q" "z" >>> </lang>

Tcl

In Tcl, optional arguments are collected when the last argument to a proc definition is called "args". The lsort command has a similar API, but with different keywords, so we adapt them.

By convention, optional parameter names in Tcl start with a leading “-” character. <lang Tcl>package require Tcl 8.5

proc tablesort {table args} {

   array set opt {-ordering "" -column 0 -reverse 0}
   array set opt $args
   set pars [list -index $opt(-column)]
   if {$opt(-reverse)} {lappend pars -decreasing}
   if {$opt(-ordering) ne ""} {lappend pars -command $opt(-ordering)}
   lsort {*}$pars $table

}

puts [tablesort $data]

  1. --> {"" q z} {a b c} {zap zip Zot}

puts [tablesort $data -column 1]

  1. --> {a b c} {"" q z} {zap zip Zot}

puts [tablesort $data -column 0]

  1. --> {"" q z} {a b c} {zap zip Zot}

puts [tablesort $data -column 0 -reverse 1]

  1. --> {zap zip Zot} {a b c} {"" q z}

puts [tablesort $data -ordering {

   apply {{a b} {expr {[string length $b]-[string length $a]}}}

}]

  1. --> {zap zip Zot} {a b c} {"" q z}</lang>