1/* File: ollama/chat.pl 2 Author: Roy Ratcliffe 3 Created: May 31 2025 4 Purpose: Ollama Chat 5 6Copyright (c) 2025, Roy Ratcliffe, Northumberland, United Kingdom 7 8Permission is hereby granted, free of charge, to any person obtaining a 9copy of this software and associated documentation files (the 10"Software"), to deal in the Software without restriction, including 11without limitation the rights to use, copy, modify, merge, publish, 12distribute, sub-license, and/or sell copies of the Software, and to 13permit persons to whom the Software is furnished to do so, subject to 14the following conditions: 15 16 The above copyright notice and this permission notice shall be 17 included in all copies or substantial portions of the Software. 18 19THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS 20OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF 21MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. 22IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY 23CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, 24TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE 25SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. 26 27*/ 28 29:- module(ollama_chat, 30 [ ollama_chat/3 % +Messages:list, -Message:dict, +Options:list 31 ]). 32:- use_module(library(http/http_open), [http_open/3]). 33:- use_module(library(http/http_client), [http_read_data/3]). 34:- use_module(library(settings), [setting/4, setting/2]). 35:- use_module(library(option), [option/3, select_option/4]). 36 37:- ensure_loaded(library(http/http_json)). 38 39:- setting(ollama_url, atom, env('OLLAMA_URL', 'http://localhost:11434/api/chat'), 40 'URL of Ollama API.'). 41:- setting(ollama_model, string, env('OLLAMA_MODEL', "nemotron-mini"), 42 'Ollama model to use.').
95:- multifile http_json:json_type/1. 96 97http_jsonjson_type(application/'x-ndjson').
stream(true)
or stream(false)
, defaulting to
streaming. This option selects the predicate's determinism.
Predicate ollama_chat/3 becomes non-deterministic when
streaming, but falls back to deterministic when not.
Pulls out the message from the reply; it becomes the result of the
chat interaction: many messages in, one message out. Taking only the
message assumes that the other keys within the reply dictionary have
less value. Callers can usually ignore them. The predicate unifies
with reply(Reply)
in the Options argument if the caller wants to
view the detailed response information.
Assumes that the reply is always a dictionary type without first checking. The implementation relies on the lower-level HTTP layers for parsing and rendering the correct term type. It also assumes that the dictionary always contains a "message" pair. Throws an exception when this presumption fails; this is a design feature because all responses must have a message.
123ollama_chat(Messages, Message, Options) :- 124 option(stream(Stream), Options, true), 125 setting(ollama_model, DefaultModel), 126 option(model(Model), Options, DefaultModel), 127 option(reply(Reply), Options, Reply), 128 setting(ollama_url, DefaultURL), 129 option(url(URL), Options, DefaultURL), 130 chat(URL, _{stream:Stream, 131 model:Model, 132 messages:Messages}, Reply, Options), 133 Message = Reply.message. 134 135chat(URL, Dict, Reply, Options) :- 136 http_open(URL, In, [post(json(Dict)), headers(Headers)|Options]), 137 call_cleanup(read_dict(In, Reply, Headers), close(In)). 138 139read_dict(In, Dict, Options) :- 140 read_data(In, Dict, [json_object(dict)|Options]), 141 ( get_dict(done, Dict, false) 142 -> true 143 ; ! 144 ). 145 146read_data(In, NotEndOfFileData, Options) :- 147 select_option(end_of_file(EndOfFile), Options, Options_, end_of_file), 148 repeat, 149 ( http_read_data([input(In)], Data, [end_of_file(EndOfFile)|Options_]), 150 Data \== EndOfFile 151 -> NotEndOfFileData = Data 152 ; !, 153 fail 154 )
Ollama Chat
Idiomatic SWI-Prolog HTTP client module for interacting with an Ollama chat API.
Usage
How to use and abuse the interface? Take some examples. The following queries run with HTTP debugging enabled. Notice the headers.
For streaming:
The streaming content type is not "application/json" but rather newline-delimited JSON. This is correct. Our addition to the JSON type multifile predicate catches this.
For non-streaming:
*/