% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(redis): Redis client} \label{sec:redis} This library is a client to \href{https://redis.io}{Redis}, a popular key value store to deal with caching and communication between micro services. In the typical use case we register the details of one or more Redis servers using \predref{redis_server}{3}. Subsequenly, \predref{redis}{2}-3 is used to issue commands on the server. For example: \begin{code} ?- redis_server(default, redis:6379, [password("secret")]). ?- redis(default, set(user, "Bob")). ?- redis(default, get(user), User). User = "Bob" \end{code} \vspace{0.7cm} \begin{description} \predicate[det]{redis_server}{3}{+ServerName, +Address, +Options} Register a redis server without connecting to it. The \arg{ServerName} acts as a lazy connection alias. Initially the \arg{ServerName} \const{default} points at \verb$localhost:6379$ with no connect options. The \const{default} server is used for \predref{redis}{1} and \predref{redis}{2} and may be changed using this predicate. \arg{Options} are described with \predref{redis_connect}{3}. Connections established this way are by default automatically reconnected if the connection is lost for some reason unless a \verb$reconnect(false)$ option is specified. \predicate[det]{redis_connect}{1}{-Connection} \nodescription \predicate[det]{redis_connect}{3}{+Address, -Connection, +Options} \nodescription \predicate[det]{redis_connect}{3}{-Connection, +Host, +Port} Connect to a redis server. The main mode is \verb$redis_connect(+Address, -Connection, +Options)$. \predref{redis_connect}{1} is equivalent to \verb$redis_connect(localhost:6379, Connection, [])$. \arg{Options}: \begin{description} \termitem{reconnect}{+Boolean} If \const{true}, try to reconnect to the service when the connection seems lost. Default is \const{true} for connections specified using \predref{redis_server}{3} and \const{false} for explictly opened connections. \termitem{user}{+User} If \verb$version(3)$ and \verb$password(Password)$ are specified, these are used to authenticate using the \arg{HELLO} command. \termitem{password}{+Password} Authenticate using \arg{Password} \termitem{version}{+Version} Specify the connection protocol version. Initially this is version 2. Redis 6 also supports version 3. When specified as \verb$3$, the \arg{HELLO} command is used to upgrade the protocol. \termitem{tls}{true} When specified, initiate a TLS connection. If this option is specified we must also specify the \const{cacert}, \const{key} and \const{cert} options. \termitem{cacert}{+File} CA Certificate file to verify with. \termitem{cert}{+File} Client certificate to authenticate with. \termitem{key}{+File} Private key file to authenticate with. \termitem{sentinels}{+ListOfAddresses} Used together with an \arg{Address} of the form \verb$sentinel(MasterName)$ to enable contacting a network of Redis servers guarded by a sentinel network. \termitem{sentinel_user}{+User} \termitem{sentinel_password}{+Password} Authentication information for the senitels. When omitted we try to connect withour authentication. \end{description} Instead of using these predicates, \predref{redis}{2} and \predref{redis}{3} are normally used with a \textit{server name} argument registered using \predref{redis_server}{3}. These predicates are meant for creating a temporary paralel connection or using a connection with a \textit{blocking} call. \begin{arguments} \arg{Address} & is a term \arg{Host}:\arg{Port}, \verb$unix(File)$ or the name of a server registered using \predref{redis_server}{3}. The latter realises a \textit{new} connection that is typically used for blocking redis commands such as listening for published messages, waiting on a list or stream. \\ \end{arguments} \begin{tags} \tag{Compatibility} \verb$redis_connect(-Connection, +Host, +Port)$ provides compatibility to the original GNU-Prolog interface and is equivalent to \verb$redis_connect(Host:Port, Connection, [])$. \end{tags} \predicate[semidet]{tls_verify}{5}{+SSL, +ProblemCert, +AllCerts, +FirstCert, +Status} Accept or reject the certificate verification. Similar to the Redis command line client (\verb$redis-cli$), we accept the certificate as long as it is signed, not verifying the hostname. \predicate[det]{redis_disconnect}{1}{+Connection} \nodescription \predicate[det]{redis_disconnect}{2}{+Connection, +Options} Disconnect from a redis server. The second form takes one option, similar to \predref{close}{2}: \begin{description} \termitem{force}{Force} When \const{true} (default \const{false}), do not raise any errors if \arg{Connection} does not exist or closing the connection raises a network or I/O related exception. This version is used internally if a connection is in a broken state, either due to a protocol error or a network issue. \end{description} \predicate[semidet]{redis}{2}{+Connection, +Request} This predicate is overloaded to handle two types of requests. First, it is a shorthand for \verb$redis(Connection, Command, _)$ and second, it can be used to exploit Redis \textit{pipelines} and \textit{transactions}. The second form is acticated if \arg{Request} is a \textit{list}. In that case, each element of the list is either a term \verb$Command -> Reply$ or a simple \arg{Command}. Semantically this represents a sequence of \predref{redis}{3} and \predref{redis}{2} calls. It differs in the following aspects: \begin{itemize} \item All commands are sent in one batch, after which all replies are read. This reduces the number of \textit{round trips} and typically greatly improves performance. \item If the first command is \const{multi} and the last \const{exec}, the commands are executed as a Redis \textit{transaction}, i.e., they are executed \textit{atomically}. \item If one of the commands returns an error, the subsequent commands \textbf{are still executed}. \item You can not use variables from commands earlier in the list for commands later in the list as a result of the above execution order. \end{itemize} Procedurally, the process takes the following steps: \begin{enumerate} \item Send all commands \item Read all replies and push messages \item Handle all callbacks from push messages \item Check whether one of the replies is an error. If so, raise this error (subsequent errors are lost) \item Bind all replies for the \verb$Command -> Reply$ terms. \end{enumerate} Examples \begin{code} ?- redis(default, [ lpush(li,1), lpush(li,2), lrange(li,0,-1) -> List ]). List = ["2", "1"]. \end{code} \predicate[semidet]{redis}{3}{+Connection, +Command, -Reply} Execute a redis \arg{Command} on Connnection. Next, bind \arg{Reply} to the returned result. \arg{Command} is a callable term whose functor is the name of the Redis command and whose arguments are translated to Redis arguments according to the rules below. Note that all text is always represented using UTF-8 encoding. \begin{itemize} \item Atomic values are emitted verbatim \item A term A:B:... where all arguments are either atoms, strings or integers (\textbf{no floats}) is translated into a string \verb$"A:B:..."$. This is a common shorthand for representing Redis keys. \item A term Term as prolog is emitted as "\Sneg{}u0000T\Sneg{}u0000" followed by Term in canonical form. \item Any other term is emitted as \predref{write}{1}. \end{itemize} \arg{Reply} is either a plain term (often a variable) or a term \verb$Value as Type$. In the latter form, \arg{Type} dictates how the Redis \textit{bulk} reply is translated to Prolog. The default equals to \const{auto}, i.e., as a number of the content satisfies the Prolog number syntax and as an atom otherwise. \begin{itemize} \item \verb$status(Atom)$ Returned if the server replies with \verb$+ Status$. Atom is the textual value of \arg{Status} converted to lower case, e.g., \verb$status(ok)$ or \verb$status(pong)$. \item \const{nil} This atom is returned for a NIL/NULL value. Note that if the reply is only \const{nil}, \predref{redis}{3} \textit{fails}. The \const{nil} value may be embedded inside lists or maps. \item A number Returned if the server replies an integer (":Int"), double (",Num") or big integer ("(Num") \item A string Returned on a \textit{bulk} reply. Bulk replies are supposed to be in UTF-8 encoding. The the bulk reply starts with "\Sneg{}u0000T\Sneg{}u0000" it is supposed to be a Prolog term. Note that this intepretation means it is \textbf{not} possible to read arbitrary binary blobs. \item A list of replies. A list may also contain \const{nil}. If \arg{Reply} as a whole would be \const{nil} the call fails. \item A list of \textit{pairs}. This is returned for the redis version 3 protocol "\%Map". Both the key and value respect the same rules as above. \end{itemize} Redis \textit{bulk} replies are translated depending on the \const{as} \arg{Type} as explained above. \begin{description} \termitem{string}{} \termitem{string}{Encoding} Create a SWI-Prolog string object interpreting the blob as following \arg{Encoding}. \arg{Encoding} is a restricted set of SWI-Prolog's encodings: \const{bytes} (\verb$iso_latin_1$), \const{utf8} and \const{text} (the current locale translation). \termitem{atom}{} \termitem{atom}{Encoding} As above, producing an atom. \termitem{codes}{} \termitem{codes}{Encoding} As above, producing a list of integers (Unicode code points) \termitem{chars}{} \termitem{chars}{Encoding} As above, producing a list of one-character atoms. \termitem{integer}{} \termitem{float}{} \termitem{rational}{} \termitem{number}{} Interpret the bytes as a string representing a number. If the string does not represent a number of the requested type a \verb$type_error(Type, String)$ is raised. \termitem{tagged_integer}{} Same as integer, but demands the value to be between the Prolog flags \verb$min_tagged_integer$ and \verb$max_tagged_integer$, allowing the value to be used as a dict key. \termitem{auto}{} Same as \verb$auto(atom, number)$ \termitem{auto}{AsText, AsNumber} If the bulk string confirms the syntax of \arg{AsNumber}, convert the value to the requested numberical type. Else convert the value to text according to \arg{AsText}. This is similar to the Prolog predicate \predref{name}{2}. \termitem{dict_key}{} Alias for \verb$auto(atom,tagged_integer)$. This allows the value to be used as a key for a SWI-Prolog dict. \termitem{pairs}{AsKey, AsValue} Convert a map or array of even length into pairs for which the key satisfies \arg{AsKey} and the value \arg{AsValue}. The \const{pairs} type can also be applied to a Redis array. In this case the array length must be even. This notably allows fetching a Redis \textit{hash} as pairs using \verb$HGETALL$ using version 2 of the Redis protocol. \termitem{dict}{AsKey, AsValue} Similar to \verb$pairs(AsKey, AsValue)$, but convert the resulting pair list into a SWI-Prolog dict. \arg{AsKey} must convert to a valid dict key, i.e., an atom or tagged integer. See \verb$dict_key$. \termitem{dict}{AsValue} Shorthand for \verb$dict(dict_key, AsValue)$. \end{description} Here are some simple examples \begin{code} ?- redis(default, set(a, 42), X). X = status("OK"). ?- redis(default, get(a), X). X = "42". ?- redis(default, get(a), X as integer). X = 42. ?- redis(default, get(a), X as float). X = 42.0. ?- redis(default, set(swipl:version, 8)). true. ?- redis(default, incr(swipl:version), X). X = 9. \end{code} \begin{tags} \tag{Errors} \verb$redis_error(Code, String)$ \end{tags} \predicate{redis}{1}{+Request} Connect to the default redis server, call \predref{redist}{3} using \arg{Request}, disconnect and print the result. This predicate is intended for interactive usage. \predicate[det]{redis_write}{2}{+Redis, +Command} \nodescription \predicate[det]{redis_read}{2}{+Redis, -Reply} Write command and read replies from a \arg{Redis} server. These are building blocks for subscribing to event streams. \predicate[det]{redis_get_list}{3}{+Redis, +Key, -List} \nodescription \predicate[det]{redis_get_list}{4}{+Redis, +Key, +ChunkSize, -List} Get the content of a \arg{Redis} list in \arg{List}. If \arg{ChunkSize} is given and smaller than the list length, \arg{List} is returned as a \textit{lazy list}. The actual values are requested using redis \verb$LRANGE$ requests. Note that this results in O(N\Shat{}2) complexity. Using a lazy list is most useful for relatively short lists holding possibly large items. Note that values retrieved are \textit{strings}, unless the value was added using \verb$Term as prolog$. \begin{tags} \tag{See also} \predref{lazy_list}{2} for a discussion on the difference between lazy lists and normal lists. \end{tags} \predicate[det]{redis_set_list}{3}{+Redis, +Key, +List} Associate a \arg{Redis} key with a list. As \arg{Redis} has no concept of an empty list, if \arg{List} is \verb$[]$, \arg{Key} is \textit{deleted}. Note that key values are always strings in \arg{Redis}. The same conversion rules as for \predref{redis}{1}-3 apply. \predicate[det]{redis_get_hash}{3}{+Redis, +Key, -Data:dict} \nodescription \predicate[det]{redis_set_hash}{3}{+Redis, +Key, +Data:dict} Put/get a \arg{Redis} hash as a Prolog dict. Putting a dict first deletes \arg{Key}. Note that in many cases applications will manage \arg{Redis} hashes by key. \predref{redis_get_hash}{3} is notably a user friendly alternative to the \arg{Redis} \verb$HGETALL$ command. If the \arg{Redis} hash is not used by other (non-Prolog) applications one may also consider using the \verb$Term as prolog$ syntax to store the Prolog dict as-is. \predicate[det]{redis_array_dict}{3}{?Array, ?Tag, ?Dict} Translate a Redis reply representing hash data into a SWI-Prolog dict. \arg{Array} is either a list of alternating keys and values or a list of \textit{pairs}. When translating to an array, this is always a list of alternating keys and values. \begin{arguments} \arg{Tag} & is the SWI-Prolog dict tag. \\ \end{arguments} \predicate[det]{redis_scan}{3}{+Redis, -LazyList, +Options} \nodescription \predicate[det]{redis_sscan}{4}{+Redis, +Set, -LazyList, +Options} \nodescription \predicate[det]{redis_hscan}{4}{+Redis, +Hash, -LazyList, +Options} \nodescription \predicate[det]{redis_zscan}{4}{+Redis, +Set, -LazyList, +Options} Map the \arg{Redis} \verb$SCAN$, \verb$SSCAN$, \verb$HSCAN$ and \arg{ZSCAN}` commands into a \textit{lazy list}. For \predref{redis_scan}{3} and \predref{redis_sscan}{4} the result is a list of strings. For \predref{redis_hscan}{4} and \predref{redis_zscan}{4}, the result is a list of \textit{pairs}. \arg{Options} processed: \begin{description} \termitem{match}{Pattern} Adds the \verb$MATCH$ subcommand, only returning matches for \arg{Pattern}. \termitem{count}{Count} Adds the \verb$COUNT$ subcommand, giving a hint to the size of the chunks fetched. \termitem{type}{Type} Adds the \verb$TYPE$ subcommand, only returning answers of the indicated type. \end{description} \begin{tags} \tag{See also} \predref{lazy_list}{2}. \end{tags} \predicate[nondet]{redis_current_command}{2}{+Redis, ?Command} \nodescription \predicate[nondet]{redis_current_command}{3}{+Redis, ?Command, -Properties} True when \arg{Command} has \arg{Properties}. Fails if \arg{Command} is not defined. The \predref{redis_current_command}{3} version returns the command argument specification. See \arg{Redis} documentation for an explanation. \predicate[nondet]{redis_property}{2}{+Redis, ?Property} True if \arg{Property} is a property of the \arg{Redis} server. Currently uses \verb$redis(info, String)$ and parses the result. As this is for machine usage, properties names *_human are skipped. \predicate[det]{redis_subscribe}{4}{+Redis, +Channels, -Id, +Options} Subscribe to one or more \arg{Redis} PUB/SUB channels. This predicate creates a thread using \predref{thread_create}{3} with the given \arg{Options}. Once running, the thread listens for messages. The message content is a string or Prolog term as described in \predref{redis}{3}. On receiving a message, the following message is broadcasted: \begin{code} redis(Id, Channel, Data) \end{code} If \predref{redis_unsubscribe}{2} removes the last subscription, the thread terminates. To simply print the incomming messages use e.g. \begin{code} ?- listen(redis(_, Channel, Data), format('Channel ~p got ~p~n', [Channel,Data])). true. ?- redis_subscribe(default, test, Id, []). Id = redis_pubsub_3, ?- redis(publish(test, "Hello world")). Channel test got "Hello world" 1 true. \end{code} \begin{arguments} \arg{Id} & is the thread identifier of the listening thread. Note that the \arg{Options} \verb$alias(Name)$ can be used to get a system wide name. \\ \end{arguments} \predicate[det]{redis_subscribe}{2}{+Id, +Channels} \nodescription \predicate[det]{redis_unsubscribe}{2}{+Id, +Channels} Add/remove channels from for the subscription. If no subscriptions remain, the listening thread terminates. \begin{arguments} \arg{Channels} & is either a single channel or a list thereof. Each channel specification is either an atom or a term `A:B:...`, where all parts are atoms. \\ \end{arguments} \predicate{redis_current_subscription}{2}{?Id, ?Channels} True when a PUB/SUB subscription with \arg{Id} is listening on \arg{Channels}. \end{description}