Decorate-sort-undecorate idiom

From Rosetta Code
Task
Decorate-sort-undecorate idiom
You are encouraged to solve this task according to the task description, using any language you may know.
Introduction

Suppose you have to sort a list of strings based on a property of each, called "the key", i.e. their lenghts. The most popular solution would require the use of a sorting algorithm with a custom comparator.

Now suppose that key computation is an expensive operation, for example, it might involve intensive reading of files, databases, or exchanging information over a network. In such a case, using a sorting algorithm with a custom comparator is not optimal, because the key is computed multiple times for each element in the array, once each time the element needs to be compared to another (and also requires the calculation of the key for that other).

The decorate-sort-undecorate idiom

One solution of the problem is called the "decorate-sort-undecorate" idiom, pattern or technique. It was originated and named by the Lisp community.

Suppose we want to sort the following list of words according to their lengths (the length was chosen for illustrative purposes, it is not precisely an "expensive" operation).

{"Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site"}

According to the decorate-sort-decorate idiom, we have to "decorate" each element with its key, so each element of the original list becomes a pair. Notice that the key is calculated once (and only once) for each element in the list:

{{"Rosetta", 7}, {"Code", 4}, {"is", 2}, {"a", 1}, {"programming", 11}, {"chrestomathy", 12}, {"site", 4}}

The list is then sorted according to the second element of each pair (the key), perhaps using a custom comparator:

{{"a", 1}, {"is", 2}, {"site", 4}, {"Code", 4}, {"Rosetta", 7}, {"programming", 11}, {"chrestomathy", 12}}

And finally, the list must be undecorated, we have to remove the second element of each pair (the key):

{"a", "is", "site", "Code", "Rosetta", "programming", "chrestomathy"}

So, the decoration acts as a form of memoization.

The Schwartzian transform

Randal L. Schwartz wrote an implementation of the decorate-sort-undecorate idiom in Perl in 1994, which gained much popularity in the Perl community. It was named "Schwartzian transform". Today the terms decorate-sort-undecorate and the Schwartzian transform are used interchangeably, even outside the Perl community.

The Wikipedia page states that a solution can be called a "Schwartzian transform" only if it does not use named temporary lists or arrays. The Lisp solution and even the solution shown by Schwartz actually use intermediate lists, but these lists do not have explicit names, instead they use a functional composition of map-sort-map operations.

Task

Write in your programming language, a function, procedure, method, routine, etc. to sort a list of words by length (the key function), using the decorate-sort-undecorate idiom.

  • Bonus 1. If your solution can accept the key function as a callback.
  • Bonus 2. If your solution is also a "Schwartzian transform", this is, it does not use named temporary lists/arrays.

You can, at your choice, show two solutions, the first using intermediate named lists/arrays, and the second one not using them (a Schwartzian transform)(if applicable). The first solution is sometimes more valuable, because the use of named entities makes the code clearer.

References

ALGOL 68

Algol 68 doesn't have standard mapping operators, but it is easy enough to construct some, as shown here.
Note, Algol 68 doesn't have procedure overloading but does have operator overloading.
If decorating other than STRINGs with INTs was required, different MODEs and OPs would be needed. As the MODE of the decorated result would be implied by the MODE yielded by the decorating procedure, the same names could be used for the DECORATE, UNDECORATE and SORT operators, only the name of the decorated MODE would be different.

BEGIN # Schwartzian transform - decorate a list of strings, sort them and    #
      # undecorate them                                                      #

    # being strongly typed, Algol 68 would require different modes for each  #
    # possible decoration - here we decorate a row of strings with an        #
    # integer                                                                #

    # mode to hold a decorated string                                        #
    MODE STRINGWITHINT = STRUCT( STRING v, INT d );

    # decorates a with INT values using the dp procedure                     #
    PRIO DECORATE = 1;   # DECORATE is dyadic so need a priority: use lowest #
    OP   DECORATE = ( []STRING a, PROC( STRING )INT dp )[]STRINGWITHINT:
         BEGIN
            REF[]STRINGWITHINT result = HEAP[ LWB a : UPB a ]STRINGWITHINT;
            FOR i FROM LWB a TO UPB a DO
                result[ i ] := STRINGWITHINT( a[ i ], dp( a[ i ] ) )
            OD;
            result
         END # DECORATE # ;

    # returns a undecorated                                                  #
    OP   UNDECORATE = ( []STRINGWITHINT a )[]STRING:
         BEGIN
            REF[]STRING result = HEAP[ LWB a : UPB a ]STRING;
            FOR i FROM LWB a TO UPB a DO
                result[ i ] := v OF a[ i ]
            OD;
            result
         END # UNDECORATE # ;

    # returns TRUE if a < b                                                  #
    OP   < = ( STRINGWITHINT a, b )BOOL:
                 d OF a < d OF b OR ( d OF a = d OF b AND v OF a < v OF b );
    # returns TRUE if a > b                                                  #
    OP   > = ( STRINGWITHINT a, b )BOOL:
                 d OF a > d OF b OR ( d OF a = d OF b AND v OF a > v OF b );

    # sorts a into order of each elements d and v                            #
    OP   SORT = ( []STRINGWITHINT a )[]STRINGWITHINT:
         BEGIN
            # in-place quick sort an array of STRINGWITHINTs from element lb #
            #                                                  to element ub #
            PROC quicksort = ( REF[]STRINGWITHINT a, INT lb, ub )REF[]STRINGWITHINT:
                 IF ub <= lb
                 THEN
                    # empty array or only 1 element                          #
                    a
                 ELSE
                    # more than one element, so must sort                    #
                    INT left   := lb;
                    INT right  := ub;
                    # choosing the middle element of the array as the pivot  #
                    STRINGWITHINT pivot  := a[ left + ( ( right + 1 ) - left ) OVER 2 ];
                    WHILE
                        WHILE IF left  <= ub THEN a[ left  ] < pivot ELSE FALSE FI
                        DO
                            left  +:= 1
                        OD;
                        WHILE IF right >= lb THEN a[ right ] > pivot ELSE FALSE FI
                        DO
                            right -:= 1
                        OD;
                        left <= right
                    DO
                        STRINGWITHINT t := a[ left  ];
                        a[ left  ]      := a[ right ];
                        a[ right ]      := t;
                        left           +:= 1;
                        right          -:= 1
                    OD;
                    quicksort( a, lb,   right );
                    quicksort( a, left, ub    );
                    a
                 FI # quicksort # ;
            quicksort( HEAP[ LWB a : UPB a ]STRINGWITHINT := a, LWB a, UPB a )
         END # SORT # ;


    # prints the elements of a enclosed in quotes with separating commas     #
    OP    SHOWQUOTED = ( []STRING a )VOID:
          BEGIN
             print( ( "[" ) );
             STRING separator := " ";
             FOR i FROM LWB a TO UPB a DO
                 print( ( separator, """", a[ i ], """" ) );
                 separator := ", "
             OD;
             print( ( " ]" ) )
          END # SHOWQUOTED # ;

    # task test case                                                         #
    SHOWQUOTED UNDECORATE SORT ( []STRING( "Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site" )
                               DECORATE ( ( STRING v )INT: ( UPB v - LWB v ) + 1 )
                               )

END
Output:
[ "a", "is", "Code", "site", "Rosetta", "programming", "chrestomathy" ]

C

C needs to use temporary arrays for the decorate and undecorate stages.

#include <stdio.h>
#include <stdlib.h>
#include <string.h>

typedef struct {
    const char *word;
    size_t key;
} wordkey;

int compare(const void* p1, const void* p2) {
    const int ip1 = ((wordkey *)p1)->key;
    const int ip2 = ((wordkey *)p2)->key;
    return (ip1 < ip2) ? -1 : ((ip1 > ip2) ? 1 : 0);
}

size_t length(const char *s) { return strlen(s); }

void sortWords(char **words, size_t le, size_t (*f)(const char* s)) {
    int i;
    char words2[le][15]; // to store the sorted array

    /* decorate */
    wordkey wordkeys[le];
    for (i = 0; i < le; ++i) {
        wordkeys[i] = (wordkey){words[i], f(words[i])};
    }

    /* sort (unstable) */
    qsort(wordkeys, le, sizeof(wordkey), compare);

    /* undecorate and print */
    printf("[");
    for (i = 0; i < le; ++i) {
        sprintf(words2[i], "\"%s\"", wordkeys[i].word);
        printf("%s, ", words2[i]);
    }
    printf("\b\b]\n");
}

int main() {
    char *words[7] = {'\0'};
    words[0] = "Rosetta";
    words[1] = "Code";
    words[2] = "is";
    words[3] = "a";
    words[4] = "programming";
    words[5] = "chrestomathy";
    words[6] = "site";
    sortWords(words, 7, length);
    return 0;
}
Output:
["a", "is", "Code", "site", "Rosetta", "programming", "chrestomathy"] 

C#

Linq makes this very easy. We can do this using 2 different syntaxes:

public static IEnumerable<T> Schwartzian1<T, TKey>(IEnumerable<T> source, Func<T, TKey> decorator) =>
    source.Select(item => (item, key: decorator(item)))
        .OrderBy(tuple => tuple.key)
        .Select(tuple => tuple.item);

public static IEnumerable<T> Schwartzian2<T, TKey>(IEnumerable<T> source, Func<T, TKey> decorator) =>
    from item in source
    let key = decorator(item)
    orderby key
    select item;

//Call:
string[] array = {"Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site"};
Console.WriteLine(string.Join(" ", Schwartzian1(array, i => i.Length)));
Output:
a is Code site Rosetta programming chrestomathy

C++

#include <algorithm>
#include <iostream>
#include <type_traits>
#include <vector>

template <typename Iterator, typename Function>
void decorate_sort_undecorate(Iterator begin, Iterator end, Function f) {
    using ValueType = typename std::iterator_traits<Iterator>::value_type;
    using KeyType = std::invoke_result_t<Function, ValueType>;
    using KeyValue = std::pair<KeyType, ValueType>;
    std::vector<KeyValue> tmp;
    tmp.reserve(std::distance(begin, end));
    std::transform(begin, end, std::back_inserter(tmp), [&f](ValueType& v) {
        return std::make_pair(f(v), std::move(v));
    });
    std::sort(tmp.begin(), tmp.end(), [](const KeyValue& a, const KeyValue& b) {
        return a.first < b.first;
    });
    std::transform(tmp.begin(), tmp.end(), begin,
                   [](KeyValue& p) { return std::move(p.second); });
}

int main() {
    std::string test[] = {"Rosetta",     "Code",         "is",  "a",
                          "programming", "chrestomathy", "site"};
    decorate_sort_undecorate(std::begin(test), std::end(test),
                             [](const std::string& s) { return s.size(); });
    for (const std::string& s : test)
        std::cout << s << ' ';
    std::cout << '\n';
}
Output:
a is Code site Rosetta programming chrestomathy 

Factor

Works with: Factor version 0.99

map-sort employs the decorate-sort-undecorate idiom, while sort-by does not.

USING: prettyprint sequences sorting.extras ;

{ "Rosetta" "Code" "is" "a" "programming" "chrestomathy" "site" }
[ length ] map-sort .
Output:
{
    "a"
    "is"
    "Code"
    "site"
    "Rosetta"
    "programming"
    "chrestomathy"
}

FreeBASIC

FreeBASIC doesn't normally print string lists in "quoted" form though I've added the quotes here to be consistent with the other solutions.

' Rosetta Code problem: https://rosettacode.org/wiki/Decorate-sort-undecorate_idiom
' by Jjuanhdez, 07/2023

Type map
    x As String
    y As Integer
End Type

Sub Sort(array() As map)
    Dim As Integer i, j, min
    Dim As Integer lb = Lbound(array), ub = Ubound(array)
    For i = lb To ub - 1
        min = i
        For j = i + 1 To ub
            If array(1,j).y <= array(1,min).y Then min = j
        Next j
        Swap array(min,1).x, array(i,1).x
        Swap array(1,min).y, array(1,i).y
    Next i
End Sub

Sub Schwartzian(a() As String)    
    Dim As Integer p, lb = Lbound(a), ub = Ubound(a)
    Dim As map e(lb To ub, lb To ub)
    
    ' Decorate
    For p = lb To ub
        e(p,1).x = a(p)
        e(1,p).y = Len(a(p))
    Next
    
    ' Sort
    Sort(e())
    
    ' Undecorate
    Print "[";
    For p = lb To ub
        Print !"\"" & e(p,1).x & !"\", ";
    Next
    Print Chr(8) & Chr(8) & "]"
End Sub

Dim As String words(6) = {"Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site"}
Schwartzian(words())

Sleep
Output:
["a", "is", "site", "Code", "Rosetta", "programming", "chrestomathy"]

Fōrmulæ

Fōrmulæ programs are not textual, visualization/edition of programs is done showing/manipulating structures but not text. Moreover, there can be multiple visual representations of the same program. Even though it is possible to have textual representation —i.e. XML, JSON— they are intended for storage and transfer purposes more than visualization and edition.

Programs in Fōrmulæ are created/edited online in its website.

In this page you can see and run the program(s) related to this task and their results. You can also change either the programs or the parameters they are called with, for experimentation, but remember that these programs were created with the main purpose of showing a clear solution of the task, and they generally lack any kind of validation.

Solution

Let us create an array for testing:

Decorate-sort-undecorate: The following is a solution using a decorate-sort-undecorate idiom:

Test case


Schwartzian transform: The following is a solution using a "Schwartzian transform" idiom, and it produces identical results:

Go

Go needs to use a temporary slice for the decoration part.

package main

import (
    "fmt"
    "sort"
)

type wordkey struct {
    word string
    key  int
}

func sortWords(words []string, f func(s string) int) {
    var le = len(words)

    // decorate
    wordkeys := make([]wordkey, le)
    for i := 0; i < le; i++ {
        wordkeys[i] = wordkey{words[i], f(words[i])}
    }

    // sort (stable)
    sort.SliceStable(wordkeys, func(i, j int) bool {
        return wordkeys[i].key < wordkeys[j].key
    })

    // undecorate (mutates original slice)
    for i := 0; i < le; i++ {
        words[i] = "\"" + wordkeys[i].word + "\""
    }

    fmt.Println(words)
}

func main() {
    words := []string{"Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site"}
    length := func(s string) int { return len(s) }
    sortWords(words, length)
}
Output:
["a" "is" "Code" "site" "Rosetta" "programming" "chrestomathy"]

Haskell

Haskell's standard sortOn is an implementation of this idiom. The source can be inspected at:
https://hackage.haskell.org/package/base-4.18.0.0/docs/src/Data.OldList.html#sortOn

import Data.List (sortOn)

main :: IO ()
main =
  mapM_ print $
    sortOn
      snd
      [ ("Rosetta", 7),
        ("Code", 4),
        ("is", 2),
        ("a", 1),
        ("programming", 11),
        ("chrestomathy", 12),
        ("site", 4)
      ]
Output:
("a",1)
("is",2)
("Code",4)
("site",4)
("Rosetta",7)
("programming",11)
("chrestomathy",12)

and equivalently:

import Data.List (sortOn)

main :: IO ()
main =
  mapM_ print $
    sortOn
      length
      [ "Rosetta",
        "code",
        "is",
        "a",
        "programming",
        "chrestomathy",
        "site"
      ]
Output:
"a"
"is"
"code"
"site"
"Rosetta"
"programming"
"chrestomathy"

J

J's native sort primitive always sorts on a key (which might be the list itself), such that each element of the key is calculated only once. This corresponds to APL's grade up primitive (though comparing dates on this approach vs. lisp's approach seems problematic due to deficiencies in historical evidence).

Thus, for example:

   >(/: #@>) ;:'Rosetta Code is a programming chrestomathy site'
a           
is          
Code        
site        
Rosetta     
programming 
chrestomathy

Java

import java.util.AbstractMap;
import java.util.List;
import java.util.function.Function;
import java.util.stream.Collectors;

public final class DecorateSortUndecorateIdiom {	

	public static void main(String[] args) {
		List<String> list = List.of( "Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site" );
		System.out.println(schwartzian(list, s -> s.length()));
	}
	
    /**
	 * Return a sorted list using the Schwartzian Transform
	 * which guarantees minimal use of the key extractor function.
	 * 
	 * Use this method when the key extractor function is an expensive operation.
	 */
	private static <T, R extends Comparable<R>> List<T> schwartzian(List<T> list, Function<T, R> function) {
		return list.stream().map( s -> new AbstractMap.SimpleEntry<T, R>(s, function.apply(s)) )
							.sorted( (one, two) -> one.getValue().compareTo(two.getValue()) )
							.map( p -> p.getKey() )
                            .collect(Collectors.toList());
	}	

}
Output:
[a, is, Code, site, Rosetta, programming, chrestomathy]

JavaScript

function schwartzian(array, keyFn) {
  return array
    .map((e) => [e, keyFn(e)])
    .sort((a, b) => a[1] - b[1])
    .map((e) => e[0]);
}

const example = [
  "Rosetta",
  "Code",
  "is",
  "a",
  "programming",
  "chrestomathy",
  "site",
];

console.log(schwartzian(example, (e) => e.length));
Output:
[ 'a', 'is', 'Code', 'site', 'Rosetta', 'programming', 'chrestomathy' ]

Note that Array.prototype.sort() takes an optional compare function that should return a negative integer, a positive integer or zero, depending on whether a is less than, greater than or equal to b. As is, the above implementation of schwartzian() would fail if keyFn returned a string, for example.

We could generalize schwartzian() to fallback to a comparison of the string representation of a and b, if they don't support the subtraction operator, and allow calling functions provide a custom compare function.

function schwartzian(array, keyFn, compareFn) {
  const defaultCompareFn = (a, b) =>
    a[1] - b[1] || String(a[1]).localeCompare(String(b[1]));

  return array
    .map((e) => [e, keyFn(e)])
    .sort(compareFn || defaultCompareFn)
    .map((e) => e[0]);
}

const example = [
  "Rosetta",
  "Code",
  "is",
  "a",
  "programming",
  "chrestomathy",
  "site",
];

console.log(schwartzian(example, (e) => e.length));

// keyFn is the string in reverse
console.log(schwartzian(example, (e) => Array.from(e).reverse().join("")));
Output:
[ 'a', 'is', 'Code', 'site', 'Rosetta', 'programming', 'chrestomathy' ]
[ 'a', 'Rosetta', 'Code', 'site', 'programming', 'is', 'chrestomathy' ]


Alternatively, composing a curried sortOn from a more general curried sortBy,
and preferring to simply return a value, rather than using `console.log`
which is not part of the JavaScript language itself, and is not available to all JS interpreters:

(() => {
    "use strict";

    // ----- 'SCHWARTZIAN' DECORATE-SORT-UNDECORATE ------

    // sortOn :: Ord b => (a -> b) -> [a] -> [a]
    const sortOn = f =>
        // Equivalent to sortBy(comparing(f)), but with f(x)
        // evaluated only once for each x in xs.
        // ('Schwartzian' decorate-sort-undecorate).
        xs => sortBy(
            comparing(x => x[0])
        )(
            xs.map(x => [f(x), x])
        )
        .map(x => x[1]);


    // ---------------------- TEST -----------------------
    const main = () =>
        sortOn(
            x => x.length
        )([
            "Rosetta",
            "Code",
            "is",
            "a",
            "programming",
            "chrestomathy",
            "site"
        ]);


    // --------------------- GENERIC ---------------------

    // comparing :: Ord a => (b -> a) -> b -> b -> Ordering
    const comparing = f =>
        // The ordering of f(x) and f(y) as a value
        // drawn from {-1, 0, 1}, representing {LT, EQ, GT}.
        x => y => {
            const
                a = f(x),
                b = f(y);

            return a < b ? -1 : (a > b ? 1 : 0);
        };


    // sortBy :: (a -> a -> Ordering) -> [a] -> [a]
    const sortBy = f =>
        // A copy of xs sorted by the comparator function f.
        xs => xs.slice()
        .sort((a, b) => f(a)(b));


    // ----------------- VALUE RETURNED ------------------
    return JSON.stringify(
        main(),
        null, 2
    );
})();
Output:
[
  "a",
  "is",
  "Code",
  "site",
  "Rosetta",
  "programming",
  "chrestomathy"
]

jq

Works with: jq

Also works with both jaq and gojq, the Rust and Go implementations of jq

jq has a built-in function, `sort_by(decorator)`, which in effect allows a decorator function to be specified, so that for the task at hand, one could simply write `sort_by(length)`, as illustrated below.

In the following, we also define a function (named `sort_by_decorator(decorator)`) that implements the decorate-sort-undecorate technique by "decorating" the list items with the specified decorator.

def sort_by_decorator(decorator):
  map([decorator, .])  # decorate
  | sort_by(.[0])      # sort by decorator
  | map(.[1])          # undecorate
  ;

# Illustration
["Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site"]
| sort_by(length), sort_by_decorator(length)
Output:
["a","is","Code","site","Rosetta","programming","chrestomathy"]
["a","is","Code","site","Rosetta","programming","chrestomathy"]

Julia

julia> schwartzian(arr, f) = map(t -> t[1], sort!(map(v -> (v, f(v)), arr), by = t -> t[2]))
schwartzian (generic function with 1 method)

julia> schwartzian(["Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site"], length)
7-element Vector{String}:
 "a"
 "is"
 "Code"
 "site"
 "Rosetta"
 "programming"
 "chrestomathy"

Kotlin

fun main() {
    val list = listOf("Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site")
    println(list.sortedBySchwartzian(String::length))
}

/**
 * Returns a sorted list using the Schwartzian Transform which guarantees minimal use of the
 * key extractor function. Use when the key extractor function is an expensive operation.
*/
fun <T, R: Comparable<R>> Collection<T>.sortedBySchwartzian(keyFn: (T) -> R): List<T> =
    this.map { it to keyFn(it) }
        .sortedBy { it.second }
        .map { it.first }

Output:

[a, is, Code, site, Rosetta, programming, chrestomathy]

Lua

Lua's 'table.sort' accepts a custom compare function as a second argument.

-- Decorate, sort, undecorate function
function dsu (tab, keyFunc)
    keyFunc = keyFunc or function (a, b) return a[2] < b[2] end 
    for key, value in pairs(tab) do
        tab[key] = {value, #value}
    end
    table.sort(tab, keyFunc)
    for key, value in pairs(tab) do
        tab[key] = value[1]
    end
    return tab
end

-- Use default sort order by not specifying a key function
local list = {"Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site"}
print(unpack(dsu(list)))

-- Create a custom key function and pass it as an argument
function descendingOrder (a, b)
    return a[2] > b[2]
end
print(unpack(dsu(list, descendingOrder)))
Output:
a       is      site    Code    Rosetta programming     chrestomathy
chrestomathy    programming     Rosetta Code    site    is      a

Nim

In Nim, there are several ways to sort a list either by creating an explicit temporary list or using a map-sort-map idiom.

The easiest way to sort a list of words by word length consists to use the “sortedByIt” template which eliminates the need to create a decorated list. But this is not what is required in this task.

Here is one way to sort the words by length using the decorate-sort-decorate idiom:

import std/[algorithm, sequtils]

let wordList = ["Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site"]

echo wordList.mapIt((value: it, length: it.len)).sortedByIt(it.length).mapIt(it.value)
Output:
@["a", "is", "Code", "site", "Rosetta", "programming", "chrestomathy"]

Note that words with same length will appear in the original list order. If we want them to appear in alphabetical order, we need to sort the list alphabetically first. As Nim sorting algorithm is stable, the order of items with same key value (i.e. length in this example) is preserved when sorting.

Of course, it is also possible to define a comparison function to sort by length then alphabetically and use it when sorting.

Nu

def 'sort by key' [keyfunc] {
	( each {|v| {k: ($v | do $keyfunc ), v: $v}}
	| sort-by k
	| each {get v} )
}

"Rosetta Code is a programming chrestomathy site" | split words | sort by key {str length}
Output:
╭───┬──────────────╮
│ 0 │ a            │
│ 1 │ is           │
│ 2 │ Code         │
│ 3 │ site         │
│ 4 │ Rosetta      │
│ 5 │ programming  │
│ 6 │ chrestomathy │
╰───┴──────────────╯

Perl

#!/usr/bin/perl

use strict; # https://rosettacode.org/wiki/Decorate-sort-undecorate_idiom
use warnings;
use List::AllUtils qw( nsort_by );

my @list = ("Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site");
print "@list\n";

my @sortedlist = nsort_by { length } @list;
print "@sortedlist\n";
Output:
Rosetta Code is a programming chrestomathy site
a is Code site Rosetta programming chrestomathy

Phix

with javascript_semantics
function sort_by(sequence s, integer f)
    return extract(s,custom_sort(apply(s,f),tagset(length(s))))
end function
?sort_by(split("Rosetta Code is a programming chrestomathy site"),length)

Technically that does not decorate/undecorate and instead uses an anonymous parallel array or two, but it does only calculate each length once.

Output:
{"a","is","Code","site","Rosetta","programming","chrestomathy"}

alternative

with javascript_semantics
function decorate_sort_undecorate(sequence s, integer f)
    s = columnize({s,apply(s,f)})
    s = sort_columns(s,{2,1})
    s = vslice(s,1)
    return s
--  return vslice(sort(columnize({apply(s,f),s})),2)
end function
?decorate_sort_undecorate(split("Rosetta Code is a programming chrestomathy site"),length)

Same output. The commented out line shows use of std sort by putting lengths before words and returning vslice(s,2), and making it all a one-liner.
Like the JavaScript entry but w/o any faff, both methods could also accept (say) reverse as the function, which would yield the following output:

{"a","Rosetta","Code","site","programming","is","chrestomathy"}

Python

def schwartzian(arr, f):
    return [t[0] for t in sorted([(v, f(v)) for v in arr], key=lambda t: t[1])]


TEST = ["Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site"]

print(TEST, "=>", schwartzian(TEST, len))
Output:
['Rosetta', 'Code', 'is', 'a', 'programming', 'chrestomathy', 'site'] => ['a', 'is', 'Code', 'site', 'Rosetta', 'programming', 'chrestomathy']

QBasic

Translation of: FreeBASIC
Works with: QBasic version 1.1
Works with: QuickBasic version 4.5
TYPE map
    x AS STRING * 12
    y AS INTEGER
END TYPE

SUB Schwartzian (a$())
    DIM e(0 TO 6, 0 TO 6) AS map
    
    ' Decorate
    FOR p = 0 TO 6
        e(p, 1).x = a$(p)
        e(1, p).y = LEN(a$(p))
    NEXT p
    
    ' Sort
    CALL Sort(e())
    
    ' Undecorate
    FOR p = 0 TO 6
        PRINT e(p, 1).x
    NEXT p
END SUB

SUB Sort (array() AS map)
    FOR i = 0 TO 6 - 1
        min = i
        FOR j = i + 1 TO 6
            IF array(1, j).y <= array(1, min).y THEN min = j
        NEXT j
        SWAP array(min, 1).x, array(i, 1).x
        SWAP array(1, min).y, array(1, i).y
    NEXT i
END SUB

DIM words(6) AS STRING
DATA "Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site"
FOR i = 0 TO 6
    READ words(i)
NEXT i
CALL Schwartzian(words())
END
Output:
a
is
site
Code
Rosetta
programming
chrestomathy

Quackery

  [ ]'[ temp put
    [] swap witheach
      [ dup temp share do
        dip nested join
        nested join ]
    temp release ]            is decoratewith ( [ --> [ )

  [ [] swap witheach
     [ 0 peek nested join ] ] is undecorate   ( [ --> [ )

  $ "Rosetta Code is a programming chrestomathy site" nest$

  decoratewith size
  sortwith [ dip [ 1 peek ] 1 peek > ]
  undecorate
  witheach [ echo$ sp ]
Output:
a is Code site Rosetta programming chrestomathy

Raku

It is somewhat rare to do, or even need to do an explicit schwartzian transform in Raku. You can pass a transform function to the sort operator, and it will use it to do its comparisons. As long as the transform is arity one (only takes one value,) the sort will automatically perform a schwartzian transform transparently, behind the scenes.

Here the transform .chars is arity one, so a schwartzian transform is performed automatically by the compiler.

# automatic schwartzian transform
dd <Rosetta Code is a programming chrestomathy site>.sort: *.chars;

# explicit schwartzian transform
dd <Rosetta Code is a programming chrestomathy site>.map({$_=>.chars}).sort({$^one.value cmp $^the-other.value}).map({.key});
Output:

( dd is the built in "data-dumper" function; a verbose and explicit representation of an objects contents.)

("a", "is", "Code", "site", "Rosetta", "programming", "chrestomathy").Seq
("a", "is", "Code", "site", "Rosetta", "programming", "chrestomathy").Seq

More complicated transforms may require an explicit schwartzian transform routine. An example of where an explicit transform is desirable is the schwartzian() routine in the Raku entry for the P-value_correction task.

RPL

This implementation accepts the key function as a callback but uses local named variables.

≪ → seq func
  ≪ { }
     1 seq SIZE FOR j 
         seq j GET
         DUP func EVAL
         2 →LIST 1 →LIST +
     NEXT   
≫ ≫ 'DECOR' STO

≪ IF DUP SIZE 2 ≥ THEN
     LIST→ → len 
     ≪ len 1 FOR n 
           1 n 1 - START 
              DUP2 2 GET SWAP 2 GET
              IF < THEN SWAP END 
              n ROLLD 
           NEXT n ROLLD  
       -1 STEP len →LIST
     ≫ END
≫ 'KSORT' STO

≪ → seq 
  ≪ { }
     1 seq SIZE FOR j 
         seq j GET 1 GET +
     NEXT   
≫ ≫ 'UNDECOR' STO
{ "Rosetta" "Code" "is" "a" "programming" "chrestomathy" "site" } ≪ SIZE ≫ DECOR KSORT UNDECOR
Output:
1: {"a" "is" "Code" "site" "Rosetta" "programming" "chrestomathy" }

Ruby

Arrays have a sort_by method which does a Schwartzian transform.

p "Rosetta Code is a programming chrestomathy site".split.sort_by(&:size)
# sort by word-size, then lexical:
str = "Rosetta Code is a programming chrestomathy site seven extra words added to this demo"
p str.split.sort_by{|word| [word.size, word]}
Output:
["a", "is", "Code", "site", "Rosetta", "programming", "chrestomathy"]
["a", "is", "to", "Code", "demo", "site", "this", "added", "extra", "seven", "words", "Rosetta", "programming", "chrestomathy"]

Rust

use itertools::sorted;

// sort by decorator using builtin function sort_by_cached_key
fn sort_by_cached(mut arr: Vec<&str>, decorator: impl Fn(&str) -> usize) -> Vec<&str> {
    arr.sort_by_cached_key(|t| decorator(*t));
    return arr;
}

// sort by decorator using Schwartzian transform
fn sort_by_decorator(arr: Vec<&str>, decorator: impl Fn(&str) -> usize) -> Vec<&str> {
    return sorted(
        arr
            .iter()
            .map(|e| (decorator(e), *e))
            .collect::<Vec<(usize, &str)>>()
    )
        .map(|e| e.1)
        .collect::<Vec<&str>>();
}

fn main() {
    let arr = Vec::from(["Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site"]);
    println!("{:?} => ", arr);
    println!(
        "    cached:    {:?}",
        sort_by_cached(arr.clone(), |x| x.len())
    );
    println!(
        "    transform: {:?}",
        sort_by_decorator(arr, |x| x.len())
    );
}
Output:
["Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site"] => 
    cached:    ["a", "is", "Code", "site", "Rosetta", "programming", "chrestomathy"]
    transform: ["a", "is", "Code", "site", "Rosetta", "programming", "chrestomathy"]

Sidef

var str = "Rosetta Code is a programming chrestomathy site"

# Built-in
say str.split.sort_by{.len}

# Same thing explicitly
say str.split.map {|w| [w, w.len] }.sort{|a,b| a[1] <=> b[1] }.map { _[0] }

# Sort by word length, then lexical:
var str2 = str+" seven extra words added to this demo"
say str2.split.sort_by{|word| [word.len, word] }
Output:
["a", "is", "Code", "site", "Rosetta", "programming", "chrestomathy"]
["a", "is", "Code", "site", "Rosetta", "programming", "chrestomathy"]
["a", "is", "to", "Code", "demo", "site", "this", "added", "extra", "seven", "words", "Rosetta", "programming", "chrestomathy"]

Wren

Wren doesn't normally print string lists in "quoted" form though I've added the quotes here to be consistent with the other solutions.

It's not specified how words of equal length are to be sorted. The standard sort() method used here (quicksort under the hood) is unstable and so the sort order for such words is not guaranteed.

var schwartzian = Fn.new { |a, f|
    System.print(a.map  { |e| [e, f.call(e)] }  // decorate
                  .toList
                  .sort { |p, q| p[1] < q[1] }  // sort
                  .map  { |p| "\"%(p[0])\""  }  // undecorate
                  .toList)
}

var words = ["Rosetta", "Code", "is", "a", "programming", "chrestomathy", "site"]
var length = Fn.new { |s| s.count }
schwartzian.call(words, length)
Output:
["a", "is", "site", "Code", "Rosetta", "programming", "chrestomathy"]

XPL0

include xpllib;         \for StrLen and StrSort
int  A, Len, I;
char B;
[A:= [" Rosetta"," Code"," is"," a"," programming"," chrestomathy"," site"];
Len:= 7;
B:= A;                  \to access bytes instead of integers
for I:= 0 to Len-1 do   \decorate
    B(I,0):= StrLen(A(I))-1;
StrSort(A, Len);
for I:= 0 to Len-1 do
    [B(I,0):= ^ ;       \undecorate
    Text(0, A(I));
    ];
]
Output:
 a is Code site Rosetta programming chrestomathy