1/* File: canny/docker.pl 2 Author: Roy Ratcliffe 3 Created: Jul 11 2025 4 Purpose: Docker API 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(canny_docker, 30 [ docker/2, % +Ask, -Reply 31 docker/3, % +Operation, -Reply, +Options 32 docker_path_options/3 % ?Operation, -Path, -Options 33 ]). 34:- use_module(library(apply), [maplist/3, convlist/3]). 35:- use_module(library(atom), [restyle_identifier/3]). 36:- use_module(library(lists), [append/3, member/2]). 37:- use_module(library(option), [select_option/4, option/2, select_option/3]). 38:- use_module(library(http/http_client), [http_get/3]). 39:- use_module(library(http/json), [json_read_dict/2]). 40:- use_module(library(settings), [setting/4, setting/2]). 41:- use_module(placeholders). 42 43:- setting(daemon_url, list, [ protocol(tcp), 44 host(localhost), 45 port(2375) 46 ], 'URL of Docker API'). 47:- setting(api_version, atom, 'v1.49', 'Version of Docker API').
The Docker API request comprises:
This implies that, for the least amount of additional information, a request is just a path with a method, e.g., a GET, HEAD or DELETE request. From that point onward, requests grow in complexity involving or more of the following: path placeholders, query parameters, a request body.
The complexity of the request can vary significantly based on the operation being performed and the specific requirements of the Docker API. The docker/2 predicate is designed to handle these variations and provide a consistent interface for interacting with the Docker API. It abstracts away the details of constructing the request and processing the response, allowing users to focus on the high-level operation they want to perform. Path placeholders appear in the first Ask term argument as atomic values. URL query parameters are specified as a list of key-value pairs in the Ask term argument. POST request payloads are specified as a Prolog dictionary as the Ask term.
The Ask term is a compound term that specifies the operation to
perform, such as container_list
or system_ping
. The Reply is a
Prolog term that represents the response from the Docker API, which
is typically a Prolog dictionary or list, depending on the operation.
The predicate constructs the URL and options based on the operation
and the settings defined in this module. It uses the ask/4 predicate
to determine the path, method, and any additional options required for
the request. The URL is constructed by appending the path to the
daemon_url
setting, and the HTTP request is made using the
http_get/3 predicate from the HTTP client library.
The Reply is then processed to ensure that the keys in the response are transformed to CamelCase format using the restyle_value/3 predicate. This transformation is useful for ensuring that the keys in the response match the expected format for the Docker API, making it easier to work with the API and ensuring compatibility with the expected response format.
276docker(Ask, Reply) :- 277 Ask =.. [Functor|Arguments], 278 ask(Arguments, Functor, URL_, Options), 279 setting(daemon_url, URL0), 280 append(URL_, URL0, URL), 281 http_get(URL, Reply0, [json_object(dict)|Options]), 282 restyle_value(one_two, Reply0, Reply). 283 284ask([], Functor, [path(Path)], Options) :- 285 ask(Functor, [Path], [], _, Options). 286ask([Value], Functor, [path(Path)], Options) :- 287 atomic(Value), 288 ask(Functor, Terms, [Placeholder], _, Options), 289 !, 290 Placeholder =.. [_, Value], 291 atomic_list_concat(Terms, '', Path). 292ask([Queries], Functor, [path(Path), search(Searches)], Options) :- 293 is_list(Queries), 294 ask(Functor, [Path], [], Queries0, Options), 295 !, 296 convlist(query_search(Queries0), Queries, Searches). 297ask([Dict], Functor, [path(Path)], [post(json(Body))|Options]) :- 298 is_dict(Dict), 299 ask(Functor, Terms, [], _, Options), 300 !, 301 option(method(post), Options), 302 atomic_list_concat(Terms, '', Path), 303 restyle_body(Dict, Body). 304ask([Value, Queries], Functor, [path(Path), search(Searches)], Options) :- 305 atomic(Value), 306 is_list(Queries), 307 ask(Functor, Terms, [Placeholder], Queries0, Options), 308 !, 309 Placeholder =.. [_, Value], 310 atomic_list_concat(Terms, '', Path), 311 convlist(query_search(Queries0), Queries, Searches). 312ask([Value, Dict], Functor, [path(Path)], [post(json(Body))|Options]) :- 313 atomic(Value), 314 is_dict(Dict), 315 ask(Functor, Terms, [Placeholder], _, Options), 316 !, 317 option(method(post), Options), 318 % Placeholder is a one-arity functor that will be unified with 319 % the Value argument. The placeholder is used to construct the 320 % path, and the Value is the argument that replaces the placeholder. 321 Placeholder =.. [_, Value], 322 atomic_list_concat(Terms, '', Path), 323 restyle_body(Dict, Body). 324ask([ Queries, Dict 325 ], Functor, [ path(Path), search(Searches) 326 ], [post(json(Body))|Options]) :- 327 % Handle a list of queries for the path plus a dictionary for the request 328 % body. The queries are used to construct the search parameters for the 329 % request, and the dictionary is used to construct the request body. 330 is_list(Queries), 331 is_dict(Dict), 332 ask(Functor, [Path], [], Queries0, Options), 333 !, 334 % The cut is not strictly necessary, but it ensures that 335 % no further clauses are considered, should any be added in future. 336 option(method(post), Options), 337 convlist(query_search(Queries0), Queries, Searches), 338 restyle_body(Dict, Body). 339 340query_search(Queries, Search, Search) :- 341 Search =.. [Name, _], 342 Query =.. [Name, _], 343 option(Query, Queries). 344 345restyle_body(Body0, Body), del_dict(labels, Body0, Labels, Dict0) => 346 restyle_value('OneTwo', Dict0, Dict), 347 put_dict(labels, Dict, Labels, Body). 348restyle_body(Body0, Body) => 349 restyle_value('OneTwo', Body0, Body).
container_list
or
system_ping
. The Terms are a list of terms that represent the atom spans
and placeholders in the operation's path. The Placeholders are a list of
one-arity functors that will be unified in the path Terms with their
corresponding arguments. The Queries are a list of terms that represent
additional search parameters for the request. The Options are a list of
terms that control how the HTTP request is made.
363ask(Operation, Terms, Placeholders, Queries, Options) :-
364 docker_path_options(Operation, Path, Options0),
365 select_option(query(Queries), Options0, Options),
366 atom_codes(Path, Codes),
367 phrase(placeholders([], Terms, [], Placeholders), Codes).
The goal is applied to each key-value pair in the input dictionary, and the results are collected into a new dictionary. The keys and values may be transformed according to the goal. This is useful for applying transformations to dictionary entries, such as changing the style of keys or values, or filtering out certain entries based on specific criteria.
The predicate uses dict_pairs/3 to convert the dictionary into a list of key-value pairs, applies the goal to each pair using maplist/3, and then converts the list of transformed pairs back into a dictionary using dict_pairs/3 again. This allows for flexible and efficient processing of dictionary entries without needing to manually iterate over the keys and values.
408:- meta_predicate mapdict( , , ). 409 410mapdict(Goal, Dict0, Dict) :- 411 dict_pairs(Dict0, _, Pairs0), 412 maplist(Goal, Pairs0, Pairs), 413 dict_pairs(Dict, _, Pairs).
The predicate takes a style identifier and a key-value pair, and it returns a new key-value pair with the key transformed according to the specified style. If the value is a dictionary, it recursively applies the same transformation to all key-value pairs within that dictionary. The transformation is useful for adapting keys to different naming conventions, such as converting from snake_case to camelCase or vice versa.
442restyle_key(Style, Key0-Value0, Key-Value) :- 443 % What if the value is a list? And what if the list contains dictionaries? 444 % Should we apply the restyling to each element? What if the list contains 445 % sub-lists? Should we apply the restyling to each element of the sub-lists? 446 % 447 % If the value is a list, apply restyle_value recursively to each element. 448 % This handles lists of dictionaries and nested lists. 449 restyle_identifier(Style, Key0, Key), 450 restyle_value(Style, Value0, Value). 451 452restyle_value(Style, Value0, Value) :- 453 ( is_dict(Value0) 454 -> mapdict(restyle_key(Style), Value0, Value) 455 ; is_list(Value0) 456 -> maplist(restyle_value(Style), Value0, Value) 457 ; Value = Value0 458 ).
container_list
or system_ping
. The
predicate constructs the URL and options based on the operation and
the settings defined in this module.
Builds HTTP request options for the Docker API using the base URL from
the daemon_url
setting. The path and HTTP method are determined by
path_and_method/4, and the resulting options are suitable for making
requests to the Docker API.
The predicate constructs the URL by concatenating the base URL with
the path and method. The daemon_url
setting provides the base URL,
and the api_version
setting specifies the version of the Docker API.
487docker(Operation, Reply, Options) :-
488 setting(daemon_url, URL),
489 setting(api_version, Version),
490 docker_path_options(Version, Operation, Path_, Options_),
491 format_path(Path_, Path, Options),
492 select_option(search(Search), Options, Options0, []),
493 append(Options0, Options_, Options__),
494 http_get([path(Path), search(Search)|URL], Reply, Options__).
{name}
and are substituted with the corresponding value for name
found in Options. The final path is formed by concatenating all
components after substitution.
The format string can contain any number of placeholders, each
enclosed in curly braces, such as {name}
. When constructing the
path, the predicate scans the format string from left to right,
replacing each placeholder with the value associated with the
corresponding key in the options list. The options list is expected
to contain terms of the form name(Value)
, where name
matches the
placeholder. All non-placeholder text in the format string is
preserved as-is.
Placeholders are substituted in the order they appear in the format string, allowing for flexible and dynamic path construction. If a placeholder is found in the format string but no corresponding value exists in the options list, the predicate fails, ensuring that all required values are provided.
This mechanism enables the dynamic generation of API paths or file
paths without hardcoding specific values, making the code more
maintainable and adaptable to changes in configuration or runtime
parameters. For example, given a format string
'/containers/{id}/json'
and options [id('abc123')]
, the
resulting path would be '/containers/abc123/json'
.
530format_path(Format, Path, Options) :- 531 format_placeholders(Format, Path, Options). 532 533 /******************************* 534 * DOCKER API * 535 *******************************/
The predicate uses the docker_path_options/4 predicate to construct the path and options for the specified operation. It retrieves the operation details from the Docker API specification and formats the path according to the specified version and operation. The resulting path and options can be used with the HTTP client to make requests to the Docker API.
build_prune | '/v1.49/build/prune' | post |
config_create | '/v1.49/configs/create' | post |
config_delete | '/v1.49/configs/{id}' | delete |
config_inspect | '/v1.49/configs/{id}' | get |
config_list | '/v1.49/configs' | get |
config_update | '/v1.49/configs/{id}/update' | post |
For container operations, the following paths and options are defined:
container_archive | '/v1.49/containers/{id}/archive' | get |
container_archive_info | '/v1.49/containers/{id}/archive' | head |
container_attach | '/v1.49/containers/{id}/attach' | post |
container_attach_websocket | '/v1.49/containers/{id}/attach/ws' | get |
container_changes | '/v1.49/containers/{id}/changes' | get |
container_create | '/v1.49/containers/create' | post |
container_delete | '/v1.49/containers/{id}' | delete |
container_exec | '/v1.49/containers/{id}/exec' | post |
container_export | '/v1.49/containers/{id}/export' | get |
container_inspect | '/v1.49/containers/{id}/json' | get |
container_kill | '/v1.49/containers/{id}/kill' | post |
container_list | '/v1.49/containers/json' | get |
container_logs | '/v1.49/containers/{id}/logs' | get |
container_pause | '/v1.49/containers/{id}/pause' | post |
container_prune | '/v1.49/containers/prune' | post |
container_rename | '/v1.49/containers/{id}/rename' | post |
container_resize | '/v1.49/containers/{id}/resize' | post |
container_restart | '/v1.49/containers/{id}/restart' | post |
container_start | '/v1.49/containers/{id}/start' | post |
container_stats | '/v1.49/containers/{id}/stats' | get |
container_stop | '/v1.49/containers/{id}/stop' | post |
container_top | '/v1.49/containers/{id}/top' | get |
container_unpause | '/v1.49/containers/{id}/unpause' | post |
container_update | '/v1.49/containers/{id}/update' | post |
container_wait | '/v1.49/containers/{id}/wait' | post |
put_container_archive | '/v1.49/containers/{id}/archive' | put |
For distribution operations, the following paths and options are defined:
distribution_inspect | '/v1.49/distribution/{name}/json' | get |
For exec operations, the following paths and options are defined:
exec_inspect | '/v1.49/exec/{id}/json' | get |
exec_resize | '/v1.49/exec/{id}/resize' | post |
exec_start | '/v1.49/exec/{id}/start' | post |
For image operations, the following paths and options are defined:
image_build | '/v1.49/build' | post |
image_commit | '/v1.49/commit' | post |
image_create | '/v1.49/images/create' | post |
image_delete | '/v1.49/images/{name}' | delete |
image_get | '/v1.49/images/{name}/get' | get |
image_get_all | '/v1.49/images/get' | get |
image_history | '/v1.49/images/{name}/history' | get |
image_inspect | '/v1.49/images/{name}/json' | get |
image_list | '/v1.49/images/json' | get |
image_load | '/v1.49/images/load' | post |
image_prune | '/v1.49/images/prune' | post |
image_push | '/v1.49/images/{name}/push' | post |
image_search | '/v1.49/images/search' | get |
image_tag | '/v1.49/images/{name}/tag' | post |
For network operations, the following paths and options are defined:
network_connect | '/v1.49/networks/{id}/connect' | post |
network_create | '/v1.49/networks/create' | post |
network_delete | '/v1.49/networks/{id}' | delete |
network_disconnect | '/v1.49/networks/{id}/disconnect' | post |
network_inspect | '/v1.49/networks/{id}' | get |
network_list | '/v1.49/networks' | get |
network_prune | '/v1.49/networks/prune' | post |
For node operations, the following paths and options are defined:
node_delete | '/v1.49/nodes/{id}' | delete |
node_inspect | '/v1.49/nodes/{id}' | get |
node_list | '/v1.49/nodes' | get |
node_update | '/v1.49/nodes/{id}/update' | post |
For plugin operations, the following paths and options are defined:
plugin_create | '/v1.49/plugins/create' | post |
plugin_delete | '/v1.49/plugins/{name}' | delete |
plugin_disable | '/v1.49/plugins/{name}/disable' | post |
plugin_enable | '/v1.49/plugins/{name}/enable' | post |
plugin_inspect | '/v1.49/plugins/{name}/json' | get |
plugin_list | '/v1.49/plugins' | get |
plugin_pull | '/v1.49/plugins/pull' | post |
plugin_push | '/v1.49/plugins/{name}/push' | post |
plugin_set | '/v1.49/plugins/{name}/set' | post |
plugin_upgrade | '/v1.49/plugins/{name}/upgrade' | post |
get_plugin_privileges | '/v1.49/plugins/privileges' | get |
secret_create | '/v1.49/secrets/create' | post |
secret_delete | '/v1.49/secrets/{id}' | delete |
secret_inspect | '/v1.49/secrets/{id}' | get |
secret_list | '/v1.49/secrets' | get |
secret_update | '/v1.49/secrets/{id}/update' | post |
For service operations, the following paths and options are defined:
service_create | '/v1.49/services/create' | post |
service_delete | '/v1.49/services/{id}' | delete |
service_inspect | '/v1.49/services/{id}' | get |
service_list | '/v1.49/services' | get |
service_logs | '/v1.49/services/{id}/logs' | get |
service_update | '/v1.49/services/{id}/update' | post |
For session operations, the following paths and options are defined:
session | '/v1.49/session' | post |
For swarm operations, the following paths and options are defined:
swarm_init | '/v1.49/swarm/init' | post |
swarm_inspect | '/v1.49/swarm' | get |
swarm_join | '/v1.49/swarm/join' | post |
swarm_leave | '/v1.49/swarm/leave' | post |
swarm_unlock | '/v1.49/swarm/unlock' | post |
swarm_unlockkey | '/v1.49/swarm/unlockkey' | get |
swarm_update | '/v1.49/swarm/update' | post |
For system operations, the following paths and options are defined:
system_auth | '/v1.49/auth' | post |
system_data_usage | '/v1.49/system/df' | get |
system_events | '/v1.49/events' | get |
system_info | '/v1.49/info' | get |
system_ping | '/v1.49/_ping' | get |
system_ping_head | '/v1.49/_ping' | head |
system_version | '/v1.49/version' | get |
For task operations, the following paths and options are defined:
task_inspect | '/v1.49/tasks/{id}' | get |
task_list | '/v1.49/tasks' | get |
task_logs | '/v1.49/tasks/{id}/logs' | get |
For volume operations, the following paths and options are defined:
volume_create | '/v1.49/volumes/create' | post |
volume_delete | '/v1.49/volumes/{name}' | delete |
volume_inspect | '/v1.49/volumes/{name}' | get |
volume_list | '/v1.49/volumes' | get |
volume_prune | '/v1.49/volumes/prune' | post |
volume_update | '/v1.49/volumes/{name}' | put |
706docker_path_options(Operation, Path, Options) :-
707 setting(api_version, Version),
708 docker_path_options(Version, Operation, Path, Options).
723docker_path_options(Version, Operation, Path, [method(Method)|Options]) :-
724 % Look up the operation in the Docker API specification. Fail if not found.
725 % Support variable Operation for dynamic queries.
726 ( var(Operation)
727 -> operation(Version, Operation, Path_, Method, Options)
728 ; once(operation(Version, Operation, Path_, Method, Options))
729 ),
730 atom_concat(/, Version, Path0),
731 atom_concat(Path0, Path_, Path).
The predicate succeeds if the given operation is present in the load_docker_api_json/2 dictionary. The dictionary is read from a JSON file that contains the Docker API specification.
753% Tablise the operation/5 predicate to allow for efficient retrieval of 754% operations based on the version, operation name, path, method, and options. It 755% allows for quick lookups of operations without needing to repeatedly parse the 756% Docker API JSON specification. 757:- table operation/5. 758 759operation(Version, Operation, Path, Method, Options) :- 760 load_docker_api_json(Version, Dict), 761 path_and_method(Dict.paths, Path, Method, MethodDict), 762 get_dict(operationId, MethodDict, OperationId), 763 restyle_identifier(one_two, OperationId, Operation), 764 dict_pairs(MethodDict, _, Pairs), 765 convlist(method_option, Pairs, Options). 766 767method_option(produces-Produces, accept(Produces)). 768method_option(parameters-Parameters, query(Terms)) :- 769 convlist(query_parameter, Parameters, Terms).
in
, name
, and type
. The predicate constructs a term of the form
`Name(Type) where
Name` is the name of the parameter and Type is its type.
778query_parameter(Parameter, Term) :-
779 _{in:"query", name:Name, type:Type} :< Parameter,
780 atom_string(Name_, Name),
781 atom_string(Type_, Type),
782 Term =.. [Name_, Type_].
798path_and_method(Paths, Path, Method, MethodDict) :-
799 dict_pairs(Paths, _, PathPairs),
800 member(Path-PathDict, PathPairs),
801 dict_pairs(PathDict, _, MethodPairs),
802 member(Method-MethodDict, MethodPairs).
The predicate uses the docker_api_json_path/2 predicate to resolve the file path relative to the current module's source file directory.
823load_docker_api_json(Version, Dict) :-
824 docker_api_json_path(Version, Abs),
825 setup_call_cleanup(open(Abs, read, In),
826 json_read_dict(In, Dict),
827 close(In)).
.json
extension. The
predicate uses the context_file/3 predicate to resolve the file
path relative to the current module's source file directory.
The Docker JSON file stores the configuration and metadata API for
Docker. Provide the base version name without the .json
extension; the predicate automatically appends it. The predicate
unifies the absolute path to the term at Abs. The context_file/3
predicate is used to resolve the file path relative to the current
module's source file directory.
850docker_api_json_path(Base, Abs) :- 851 file_name_extension(Base, json, Name), 852 context_file((..)/docker/Name, Abs, [access(exist)]). 853 854 /******************************* 855 * CONTEXT * 856 *******************************/
869context_file(Spec, Abs, Options) :-
870 context_module(M),
871 module_property(M, file(File)),
872 file_directory_name(File, Directory),
873 absolute_file_name(Spec, Abs, [relative_to(Directory)|Options])
Canny Docker
This module provides an interface to the Docker API, allowing interaction with Docker services through HTTP requests. It defines settings for the Docker daemon URL and API version, and provides a predicate to construct URLs and options for various Docker operations.
It supports operations such as listing containers, creating containers, and checking the Docker system status. The module uses Prolog dictionaries to represent JSON data structures, making it easy to work with the Docker API's responses. It also includes utility predicates for transforming dictionary key-value pairs and constructing paths for API requests. It is designed to be used in conjunction with the HTTP client library to make requests to the Docker API. It provides a flexible way to interact with Docker services, allowing for dynamic construction of API requests based on the specified operations and options.
Docker API Operations
The module supports various Docker API operations, such as:
system_ping
: Check if the Docker daemon is reachable.container_list
: List all containers.container_create
: Create a new container.network_create
: Create a new network.network_delete
: Delete a network.These operations are defined in the Docker API specification and can be accessed through the docker/3 predicate, which constructs the appropriate URL and options based on the operation and the settings defined in this module.
Example container operations
The following examples demonstrate how to list and create Docker containers using the docker/3 predicate. The first example lists all containers, and the second example creates a new container with a specified image and labels.
The container_list/2 predicate retrieves a list of all containers, returning a list of dictionaries representing each container. Each dictionary contains information such as the container ID, image, and other metadata. The container_create/3 predicate creates a new container with the specified image and labels. The labels are specified as a JSON object, allowing for flexible tagging of containers with metadata. The reply contains the ID of the created container and any warnings that may have occurred during the creation process. The labels can be used to organise and manage containers based on specific criteria, such as purpose or owner.
Example network operations
The following examples demonstrate how to create and delete a Docker network using the docker/3 predicate. The network is created with a name and labels, and then deleted by its name.
Note that the network_create/2 predicate constructs a network with the specified name and labels, and returns a reply containing the network ID and any warnings. The network_delete/2 predicate deletes the network by its name, returning an empty reply if successful.
Labels can be used to tag networks with metadata, which can be useful for organising and managing Docker resources. The labels are specified as a dictionary with key-value pairs, where the keys and values are strings. The labels are included in the network configuration when creating a network, allowing for flexible and dynamic tagging of Docker resources.
Labels can be used to filter and query networks, making it easier to manage Docker resources based on specific criteria. For example, you can create a network with a label indicating its purpose or owner, and then use that label to find networks that match certain criteria. This allows for more organised and efficient management of Docker resources, especially in larger deployments with many networks and containers.
Restyling Keys
The docker/3 predicate transforms the keys in the input dictionary to CamelCase format using the restyle_key/3 predicate, which applies the Docker-specific CamelCase naming convention to the keys. This transformation is useful for ensuring that the keys in the input dictionary match the expected format for the Docker API, making it easier to work with the API and ensuring compatibility with the expected request format.
The transformation is applied recursively to all key-value pairs in the input dictionary, ensuring that all keys are transformed to the correct format before making the request to the Docker API. The reverse transformation is applied to the reply dictionary, which does not retain the original key names as returned by the Docker API. Label keys are also transformed to CamelCase format, ensuring consistency in the naming convention used for labels in the Docker API requests and responses.
Low-Level HTTP Requests
The module provides a low-level interface to the Docker API, allowing for custom HTTP requests to be made. The docker/3 predicate constructs the URL and options for the specified operation, and uses the http_get/3 predicate to make the request. The options can include HTTP methods, headers, and other parameters as needed for the specific operation.
The url_options/4 predicate is used to construct the URL and options for a specific Docker operation. It retrieves the operation details from the Docker API specification and formats the path according to the specified version and operation. The resulting URL and options can be used with the HTTP client to make requests to the Docker API.
Example usage
The url_options/4 predicate can be used to construct the URL and options for a specific Docker operation. For example, to get the URL and options for the
system_ping
operation, you can use:For listing containers, you can use:
For creating a container, you can use:
This example creates a new Docker container with the specified image and labels. Notice that the post request uses
json(json(...))
to specify the JSON body of the request.