a curated list of database news from authoritative sources

November 01, 2021

Recurse Center Day 1: init

This is a draft post that I have prematurely published. Currently, I am attending RC and I want to write as much as possible, log my daily learnings and activities. But, I also don't want to spend time on grammar and prose, so I am publishing all the posts which usually I'd have kept in my draft folder.

My RC first day was filled with welcome events and fun activities. It was nice to meet all the lovely people.

October 31, 2021

October 29, 2021

Exploring PL/pgSQL part two: implementing a Forth-like interpreter

Previously in exploring PL/pgSQL:
Strings, arrays, recursion and parsing JSON

In my last post I walked through the basics of PL/pgSQL, the embedded procedural language inside of PostgreSQL. It covered simple functions, recursions and parsing. But there was something very obviously missing from that post: a working interpreter.

So in this post we'll walk through building a Forth-like language from scratch in PL/pgSQL. We'll be able to write a fibonacci function in this Forth-like language and have it be evaluated correctly like so:

$ ./test.sh sm.sql "SELECT sm_run('
DEF fib
  DUP 1 > IF
  1- DUP 1- fib CALL SWAP fib CALL + THEN
  RET

20 fib CALL
EXIT')"

...

 sm_run
--------
 6765
(1 row)

All code is available on Github.

Forth

Forth is a stack-oriented language. Literals are pushed onto the stack. Functions and builtins operate on the stack.

For example:

$ ./test.sh sm.sql "SELECT sm_run('3 2 + EXIT')"

Will produce 5. And:

$ ./test.sh sm.sql "SELECT sm_run('3 2 + 1 - EXIT')"

Will produce 4.

Our code will notably not be a real Forth, since there are many special features of a real Forth. But it will look like one to a novice Forth programmer like myself.

You can read more about Forth basics here. And you can read a truly stunning, real Forth implementation in jonesforth.S. Or you can pick up Let Over Lambda for a fantastic book on Common Lisp that culminates in a Forth interpreter.

Implementation

Since the builtin array_length($arr, $dim) returns NULL if the array is NULL and our dimension is always 1, we'll write a helper.

DROP FUNCTION IF EXISTS sm_alength;
CREATE FUNCTION sm_alength(a text[]) RETURNS int AS $$
BEGIN
  RETURN COALESCE(array_length(a, 1), 0);
END;
$$ LANGUAGE plpgsql;

We'll also need to bring in the hstore extension so we can map function names to their positions. (We could use an association list but those are less programmer-friendly.)

CREATE EXTENSION IF NOT EXISTS hstore;

Our interpreter function will take a string to evaluate, splitting the string on whitespace into tokens.

DROP FUNCTION IF EXISTS sm_run;
CREATE FUNCTION sm_run(s text) RETURNS TEXT AS $$
DECLARE
  tokens text[] = regexp_split_to_array(s, '\s+');
  stack text[]; -- Data stack
  defs hstore; -- Map of functions to location
  tmps text[]; -- Array we can use for temporary variables
  token text; -- Current token
  rps text[]; -- Return pointer stack, always ints but easier to store as text
  pc int = 1; -- Program counter
BEGIN

We set up a tmps array because each builtin may need differing number of temporary variables and PL/pgSQL makes ad-hoc variables cumbersome (or at least an easier way exists outside my knowledge).

And we store the return pointer stack as a text array so that we can use sm_alength on it even though values in this array will always be integers.

Next we'll start an infinite loop to evaluate the program. The only thing that will stop the input is the EXIT builtin that will return from this function with the top of the stack.

  WHILE true LOOP
    token = tokens[pc];
    RAISE NOTICE '[Debug] Current token: %. Current stack: %.', token, stack;
    IF token IS NULL THEN
      RAISE EXCEPTION 'PC out of bounds.';
    END IF;

    IF token = 'EXIT' THEN
      RETURN stack[sm_alength(stack)];
    END IF;

    ... TODO ...

    stack = array_append(stack, token);
    pc = pc + 1;
  END LOOP;
END;
$$ LANGUAGE plpgsql;

If no other condition is met (the token is not a builtin), we push it onto the data stack and increment the program counter.

Conditionals

The IF builtin pops the top of the stack. If it is true evaluation continues. If it is false evaluation skips ahead until after a THEN builtin.

For example:

$ ./test.sh sm.sql "SELECT sm_run('1 1 1 = IF 2 THEN EXIT')"

Produces 2. But

$ ./test.sh sm.sql "SELECT sm_run('1 1 0 = IF 2 THEN EXIT')"

Produces 1.

Implementation

Joining the EXIT condition in the interpeter loop we get:

...

  WHILE true LOOP

    ...

    IF token = 'IF' THEN
      -- Grab last item from stack
      tmps[1] = stack[sm_alength(stack)];
      -- Remove one item from stack
      stack = stack[1:sm_alength(stack) - 1];
      IF NOT tmps[1]::boolean THEN
        WHILE tokens[pc] <> 'THEN' LOOP
      pc = pc + 1;
    END LOOP;
    pc = pc + 1; -- Skip past THEN
      ELSE
        pc = pc + 1;
      END IF;
      CONTINUE;
    END IF;

    IF token = 'THEN' THEN
      -- Just skip past it
      pc = pc + 1;
      CONTINUE;
    END IF;

    IF token = 'EXIT' THEN
      RETURN stack[sm_alength(stack)];
    END IF;

    ...

Other builtins

The DUP builtin makes a copy of the top of the stack. The SWAP builtin swaps the order of the top two items on the stack. And the 1- builtin subtracts 1 from the top of the stack.

    ...

    IF token = 'DUP' THEN
      -- Grab item
      tmps[1] = stack[sm_alength(stack)];
      -- Add it to the stack
      stack = array_append(stack, tmps[1]);
      pc = pc + 1;
      CONTINUE;
    END IF;

    IF token = '1-' THEN
      -- Grab item
      tmps[1] = stack[sm_alength(stack)];
      -- Rewrite top of stack
      stack[sm_alength(stack)] = tmps[1]::int - 1;
      pc = pc + 1;
      CONTINUE;
    END IF;

    IF token = 'SWAP' THEN
      -- Grab two items from stack
      tmps[1] = stack[sm_alength(stack) - 1];
      tmps[2] = stack[sm_alength(stack)];
      -- Swap the two
      -- Replace last item on stack
      stack[sm_alength(stack)] = tmps[1];
      stack[sm_alength(stack) - 1] = tmps[2];
      pc = pc + 1;
      CONTINUE;
    END IF;

    ...

It's important that every builtin handle incrementing the program counter and skipping to the beginning of the loop. Because some builtins increment the program counter under different conditions (like IF above).

The last few builtins are the simplest: arithmetic operations that produce integers or booleans.

    ...

    IF token = '=' THEN
      -- Grab two items from stack
      tmps[1] = stack[sm_alength(stack) - 1];
      tmps[2] = stack[sm_alength(stack)];
      -- Remove one item from stack
      stack = stack[1:sm_alength(stack) - 1];
      -- Replace last item on stack
      stack[sm_alength(stack)] = tmps[1]::int = tmps[2]::int;
      pc = pc + 1;
      CONTINUE;
    END IF;

    IF token = '>' THEN
      -- Grab two items from stack
      tmps[1] = stack[sm_alength(stack) - 1];
      tmps[2] = stack[sm_alength(stack)];
      -- Remove one item from stack
      stack = stack[1:sm_alength(stack) - 1];
      -- Replace last item on stack
      stack[sm_alength(stack)] = tmps[1]::int > tmps[2]::int;
      pc = pc + 1;
      CONTINUE;
    END IF;

    IF token = '+' THEN
      -- Grab two items from stack
      tmps[1] = stack[sm_alength(stack) - 1];
      tmps[2] = stack[sm_alength(stack)];
      -- Remove one item from stack
      stack = stack[1:sm_alength(stack) - 1];
      -- Replace last item on stack
      stack[sm_alength(stack)] = tmps[1]::int + tmps[2]::int;
      pc = pc + 1;
      CONTINUE;
    END IF;

    IF token = '-' THEN
      -- Grab two items from stack
      tmps[1] = stack[sm_alength(stack) - 1];
      tmps[2] = stack[sm_alength(stack)];
      -- Remove one item from stack
      stack = stack[1:sm_alength(stack) - 1];
      -- Replace last item on stack
      stack[sm_alength(stack)] = tmps[1]::int - tmps[2]::int;
      pc = pc + 1;
      CONTINUE;
    END IF;

    IF token = '*' THEN
      -- Grab two items from stack
      tmps[1] = stack[sm_alength(stack) - 1];
      tmps[2] = stack[sm_alength(stack)];
      -- Remove one item from stack
      stack = stack[1:sm_alength(stack) - 1];
      -- Replace last item on stack
      stack[sm_alength(stack)] = tmps[1]::int * tmps[2]::int;
      pc = pc + 1;
      CONTINUE;
    END IF;

    IF token = '/' THEN
      -- Grab two items from stack
      tmps[1] = stack[sm_alength(stack) - 1];
      tmps[2] = stack[sm_alength(stack)];
      -- Remove one item from stack
      stack = stack[1:sm_alength(stack) - 1];
      -- Replace last item on stack
      stack[sm_alength(stack)] = tmps[1]::int / tmps[2]::int;
      pc = pc + 1;
      CONTINUE;
    END IF;

    ...

Function definitions

Functions here will differ from Forth, borrowing elements of machine code. Return pointers will be stored in a dedicated return pointer stack. We could store it on the data stack but that would require more effort on the part of the programmer to restore the stack. Calling RET inside a function pops a return pointer off the return pointer stack.

Here's a simple function definition: DEF plus + RET.

    ...

    IF token = 'DEF' THEN
      tmps[1] = tokens[pc+1]; -- function name
      tmps[2] = pc + 2; -- starting pc
      WHILE tokens[pc] <> 'RET' LOOP
        -- RAISE NOTICE '[Debug] skipping past: %.', tokens[pc];
        pc = pc + 1;
      END LOOP;

      IF defs IS NULL THEN
        defs = hstore(tmps[1], tmps[2]);
      ELSE
        defs = defs || hstore(tmps[1], tmps[2]);
      END IF;
      pc = pc + 1; -- continue past 'RET'
      CONTINUE;
    END IF;

    ...

There doesn't seem to be a way to combine a NULL hstore value and a non-NULL hstore value. So that's why we need that special case.

Return

The RET builtin pops a value off the return pointer stack and jumps to it.

   ...

   IF token = 'RET' THEN
      -- Grab last return pointer
      tmps[1] = rps[sm_alength(rps)];
      -- Drop last return pointer from stack
      rps = rps[1:sm_alength(rps) - 1];
      -- Jump to last return pointer
      pc = tmps[1]::int;
      CONTINUE;
    END IF;

    ...

Function calls

Forming the other half of function calls is the CALL builtin. This places the program counter (plus one, past the CALL token) onto the return pointer stack and jumps to the position of the function if it exists.

A simple function call for the above plus function might be: 2 3 plus CALL and would produce 5 on the top of the stack.

    ...

    IF token = 'CALL' THEN
      -- Grab item
      tmps[1] = stack[sm_alength(stack)];
      -- Remove one item from stack
      stack = stack[1:sm_alength(stack) - 1];
      -- Store return pointer
      rps = array_append(rps, (pc + 1)::text);
      -- Fail if function not defined
      IF NOT defs?tmps[1] THEN
        RAISE EXCEPTION 'No such function, %.', tmps[1];
      END IF;
      -- Otherwise jump to function
      RAISE NOTICE '[Debug] Jumping to: %:%.', tmps[1], defs->tmps[1];
      pc = defs->tmps[1];
      CONTINUE;
    END IF;

    ...

And that's it! All done the basic instructions needed. Store all that code in sm.sql and grab the test.sh code from the previous post:

$ cat ./test.sh
sudo -u postgres psql -c "$(printf "%s;\n%s" "$(cat $1)" "$2")"

And try out our port of recursive fibonacci:

$ ./test.sh sm.sql "SELECT sm_run('
DEF fib
  DUP 1 > IF
  1- DUP 1- fib CALL SWAP fib CALL + THEN
  RET

20 fib CALL
EXIT')"

...

 sm_run
--------
 6765
(1 row)

Happy PL/pgSQL- and Forth-ish-ing!

October 28, 2021

October 26, 2021

Announcing Vitess 12

On behalf of the Vitess maintainers, I am pleased to announce the general availability of Vitess 12. Major Themes # In this release, Vitess Maintainers have made significant progress in several areas, including Gen4 planner, VTAdmin, and other improvements. Please take a moment to review the Release Notes. Please read them carefully and report any issues via GitHub. Gen4 Planner # The newest version of the query planner, Gen4, becomes an experimental feature as part of this release.

October 24, 2021

Exploring PL/pgSQL: Strings, arrays, recursion, and parsing JSON

Next in exploring PL/pgSQL:
Implementing a Forth-like interpreter

PostgreSQL comes with a builtin imperative programming language called PL/pgSQL. I used to think this language was scary because it has a bit more adornment than your usual language does. But looking deeper, it's actually reasonably pleasant to program in.

In this post we'll get familiar with it by working with strings, arrays and recursive functions. We'll top it all off by building a parser for a subset of JSON (no nested objects, no arrays, no unicode, no decimals).

The goal here is not production-quality code (an amazing JSON library is already built into PostgreSQL) but simply to get more familiar with the PL/pgSQL language.

All code for this post is available on Github.

Creating functions

Functions are declared like tables. Here's a very simple one that returns the length of a string:

CREATE OR REPLACE FUNCTION slength(s text) RETURNS int AS $$
BEGIN
  RETURN length(s);
END;
$$ LANGUAGE plpgsql;

It's not a very useful function because length already exists but the point is to see a basic custom function.

All statements in PL/pgSQL must end in a semicolon. Arguments do not have to be named. If they are not named they get default names of $1 to $N.

Named/unnamed arguments

Here's how the function could be written without named arguments:

CREATE OR REPLACE FUNCTION slength(text) RETURNS int AS $$
BEGIN
  RETURN length($1);
END;
$$ LANGUAGE plpgsql;

Out declarations

PL/pgSQL also allows you to declare which variables will be returned in the function argument list. They call it OUT parameters but as far as I can tell it is not like OUT parameters in C# where you are modifying the value of a variable in an external scope.

CREATE OR REPLACE FUNCTION slength(s text, OUT i int) RETURNS int AS $$
BEGIN
  i = length(s);
END;
$$ LANGUAGE plpgsql;

This is still equivalent to the first function and is basically a shortcut for:

CREATE OR REPLACE FUNCTION slength(s text) RETURNS int AS $$
DECLARE
  i int;
BEGIN
  i = length(s);
  RETURN i;
END;
$$ LANGUAGE plpgsql;

Whether you declare OUT or not you still must include RETURNS <type> in the function signature otherwise even if you call RETURN in the body, the result will just be ignored.

Don't worry about case sensitivity too much. It's really only important, as in typical SQL, for mixed-case table and column names. But we won't be dealing with that situation in this article focused on programming PL/pgSQL.

Testing it out

Once the function is created, you can call it like SELECT slength('foo');. So here's a helper script to load a SQL file and run a command:

$ cat ./test.sh
sudo -u postgres psql -c "$(printf "%s;\n%s" "$(cat $1)" "$2")"
$ chmod +x ./test.sh

After storing the above slength code in slength.sql we can run a test:

$ ./test.sh ./slength.sql "SELECT slength('foo')"
 slength
---------
       3
(1 row)

Easy!

Numbers and recursion

Ok now that we've got the basics of function definition down and a way to test the code, let's write a fibonacci program.

$ cat ./fib.sql
CREATE OR REPLACE FUNCTION fib(i int) RETURNS int AS $$
BEGIN
  IF i = 0 OR i = 1 THEN
    RETURN i;
  END IF;

  RETURN fib(i - 1) + fib(i - 2);
END;
$$ LANGUAGE plpgsql;

Everything in the if test is normal SQL WHERE clause syntax. This makes it very easy for folks familiar with SQL to pick up conditionals in PL/pgSQL.

And there's no special syntax to allow function recursion. Nice!

Run and test this function:

$ ./test.sh ./fib.sql "SELECT fib(10)"
 fib
-----
  55
(1 row)

Getting the hang of it?

Strings and arrays

You may have noticed that length used in slength is a builtin PostgreSQL function for dealing with strings. All builtin functions in PostgreSQL can be used in PL/pgSQL.

In order to get familiar with using arrays in PL/pgSQL let's write a string_to_array function.

$ cat ./string_to_array.sql
CREATE OR REPLACE FUNCTION string_to_array(s text) RETURNS char[] AS $$
DECLARE
  a char[];
BEGIN
  WHILE COALESCE(array_length(a, 1), 0) < length(s) LOOP
    a[COALESCE(array_length(a, 1), 0) + 1] = substr(s, COALESCE(array_length(a, 1), 0) + 1, 1);
  END LOOP;
  RETURN a;
END;
$$ LANGUAGE plpgsql;

This is one way to do it by modify array values directly by index. We need to coalesce because calling array_length on an empty array returns NULL.

Another way to do this is by calling the builtin function array_append.

CREATE OR REPLACE FUNCTION string_to_array(s text) RETURNS char[] AS $$
DECLARE
  a char[];
BEGIN
  WHILE COALESCE(array_length(a, 1), 0) < length(s) LOOP
    a = array_append(a, substr(s, COALESCE(array_length(a, 1), 0) + 1, 1)::char);
  END LOOP;
  RETURN a;
END;
$$ LANGUAGE plpgsql;

We can test and run both:

$ ./test.sh ./string_to_array.sql "SELECT string_to_array('foo')"
 string_to_array
-----------------
 {f,o,o}
(1 row)
$ ./test.sh ./string_to_array2.sql "SELECT string_to_array('foo')"
 string_to_array
-----------------
 {f,o,o}
(1 row)

Of course the builtin alternative might be SELECT regexp_split_to_array('foo') but we need the practice.

Custom compound types

If we're going to lex and parse JSON, we're going to want to return an array of tokens from the lexer. A token will need to contain the type (e.g. number, string, syntax) and the string value of the token (e.g. 1, {, my great key).

PostgreSQL allows us to create compound types that we can then use as the base of an array:

DROP TYPE IF EXISTS json_token CASCADE;
CREATE TYPE json_token AS (
  kind text,
  value text
);

We need to add CASCADE here because functions will have this type in their signature and it otherwise makes PostgreSQL unhappy to delete the type used in a function before deleting the function.

We can create literals of this type like SELECT ('number', '12')::json_token).

Now we're ready to build out the lexer.

Lexing

The lexers job is to clump together groups of characters into tokens.

I'm going to describe this function in literate code.

CREATE OR REPLACE FUNCTION json_lex(j text, OUT ts json_token[]) RETURNS json_token[] AS $$

This function takes a string in and returns an array of json tokens.

DECLARE 
  i int = 1; -- Index in loop
  c text; -- Current character in loop
  token text; -- Current accumulated characters

We need to declare all variables up front.

BEGIN
  WHILE i < length(j) + 1 LOOP
    c = substr(j, i, 1);
    token = '';

The main loop just looks at all characters.

    -- Handle syntax characters
    IF c = '{' OR c = '}' OR c = ',' OR c = ':' THEN
      ts = array_append(ts, ('syntax', c)::json_token);
      i = i + 1;
      CONTINUE;
    END IF;

First we look if the character is a syntax character. If it is we append it to the array of tokens, increment the index, and go back to the start of the main loop.

    -- Handle whitespace
    IF regexp_replace(c, '^\s+', '') = '' THEN
      i = i + 1;
      CONTINUE;
    END IF;

Then we check for whitespace characters. If replacing all whitespace characters returns an empty string then we know it's whitespace. We could also have done something like IF c = ' ' OR c = '\n' ... THEN instead.

Same as before though if we find whitespace characters we move on (don't accumulate them) and restart the main loop.

    -- Handle strings
    IF c = '"' THEN
      i = i + 1;
      c = substr(j, i, 1);
      WHILE c <> '"' LOOP
        token = token || c;
        i = i + 1;
        c = substr(j, i, 1);
      END LOOP;

      i = i + 1;
      ts = array_append(ts, ('string', token)::json_token);
      CONTINUE;
    END IF;

Next we loop through any strings we find and accumulate them as tokens before restarting the main loop.

    -- Handle numbers
    WHILE c ~ '^[0-9]+$' LOOP
      token = token || c;
      i = i + 1;
      c = substr(j, i, 1);
    END LOOP;
    IF length(token) > 0 THEN
      ts = array_append(ts, ('number', token)::json_token);
      CONTINUE;
    END IF;

Then we look for integers.

    RAISE EXCEPTION 'Unknown character: %, at index: %; already found: %.', c, i, ts;
  END LOOP;
END;
$$ LANGUAGE plpgsql;

Lastly if none of those lexing handlers match, we give up! Then the loop is done and the function is too.

There's no RETURN statement because we already declared an OUT variable.

If we test and run this now:

./test.sh ./json.sql "SELECT json_lex('{\"flubberty\": 12, \"nice\": \"a\"}')"
                                                                json_lex
----------------------------------------------------------------------------------------------------------------------------------------
 {"(syntax,{)","(string,flubberty)","(syntax,:)","(number,12)","(syntax,\",\")","(string,nice)","(syntax,:)","(string,a)","(syntax,})"}
(1 row)

It's messy but it worked! Now on to parsing.

Parsing

Our parser will only accept JSON objects. JSON objects will be defined as an array of key-value pairs. Custom types make this nice again.

DROP TYPE IF EXISTS json_key_value CASCADE;
CREATE TYPE json_key_value AS (
  k text,
  v text
);

One thing PostgreSQL does not make nice is sum types or parametric types. But even if the value here is stored as text it can be easily cast to a number by the user. And again, we're not going to support nested objects/arrays. But using hstore for key-values might be the better alternative if we wanted to build a real JSON parser.

CREATE OR REPLACE FUNCTION json_parse(ts json_token[], i int) RETURNS json_key_value[] AS $$
DECLARE
  t json_token; -- Current token in tokens loop
  kvs json_key_value[];
  k text;
BEGIN
  t = ts[i];

  IF t.kind <> 'syntax' OR t.value <> '{' THEN
    RAISE EXCEPTION 'Invalid JSON, must be an object, got: %.', t;
  END IF;
  i = i + 1;
  t = ts[i];

First up in the parser is variable declarations and validating that this list of tokens represents a JSON object.

  WHILE t.kind <> 'syntax' OR t.value <> '}' LOOP
    IF array_length(kvs, 1) > 0 THEN
      IF t.kind <> 'syntax' OR t.value <> ',' THEN
        RAISE EXCEPTION 'JSON key-value pair must be followed by a comma or closing brace, got: %.', t;
      END IF;

      i = i + 1;
      t = ts[i];
    END IF;

Then we loop to find each key-value pair. If one has already been found, we need to find a comma before the next pair.

    IF t.kind <> 'string' THEN
      RAISE EXCEPTION 'JSON object must start with string key, got: %.', t;
    END IF;
    k = t.value;

    i = i + 1;
    t = ts[i];
    IF t.kind <> 'syntax' OR t.value <> ':' THEN
      RAISE EXCEPTION 'JSON object must start with string key followed by colon, got: %.', t;
    END IF;

    i = i + 1;
    t = ts[i];
    IF t.kind = 'number' OR t.kind = 'string' THEN
      kvs = array_append(kvs, (k, t)::json_key_value);
      i = i + 1;
      t = ts[i];
      CONTINUE;
    END IF;

    RAISE EXCEPTION 'Invalid key-value pair syntax, got: %.', t;
  END LOOP;

  RETURN kvs;
END;
$$ LANGUAGE plpgsql;

Then we just look for the key, colon, value syntax and fail if we don't see it. And that's it! Very simple when not dealing with arrays and nested objects.

Helpers

Lastly it would just be nice to have a single function that calls lex and parse:

CREATE OR REPLACE FUNCTION json_from_string(s text) RETURNS json_key_value[] AS $$
BEGIN
  RETURN json_parse(json_lex(s), 1);
END;
$$ LANGUAGE plpgsql;

And another function to look up a value in a parsed object by key:

CREATE OR REPLACE FUNCTION json_get(kvs json_key_value[], key text) RETURNS text AS $$
DECLARE
  kv json_key_value;
BEGIN
  FOREACH kv IN ARRAY kvs LOOP
    IF kv.k = key THEN RETURN (kv.v::json_token).value; END IF;
  END LOOP;

  RAISE EXCEPTION 'Key not found.';
END;
$$ LANGUAGE plpgsql;

And we're all set!

Testing

Let's try some bad syntax (missing a comma between pairs):

./test.sh ./json.sql "SELECT json_get(json_from_string('{\"flubberty\": 12 \"nice\": \"a\"}'), 'ipo')"
ERROR:  JSON key-value pair must be followed by a comma or closing brace, got: (string,nice).
CONTEXT:  PL/pgSQL function json_parse(json_token[],integer) line 18 at RAISE
PL/pgSQL function json_from_string(text) line 3 at RETURN

Sweet, it fails correctly.

Now correct syntax but missing key:

./test.sh ./json.sql "SELECT json_get(json_from_string('{\"flubberty\": 12, \"nice\": \"a\"}'), 'ipo')"
ERROR:  Key not found.
CONTEXT:  PL/pgSQL function json_get(json_key_value[],text) line 9 at RAISE

And finally, correct syntax and existing key:

./test.sh ./json.sql "SELECT json_get(json_from_string('{\"flubberty\": 12, \"nice\": \"a\"}'), 'flubberty')"
 json_get
----------
 12
(1 row)

Huzzah! Now hopefully PL/pgSQL is a little less scary to you, whether or not you decide to use it.

October 19, 2021