1/* File: canny/placeholders.pl 2 Author: Roy Ratcliffe 3 Created: Jul 19 2025 4 Purpose: Formatting Placeholders 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_placeholders, 30 [ format_placeholders/3, % +Format, -Atom, +Options 31 format_placeholders/4, % +Format, -Atom, +Options, -RestOptions 32 placeholders//2, 33 placeholders//4 34 ]). 35:- use_module(library(error), [must_be/2]). 36:- use_module(library(lists), [append/3]). 37:- use_module(library(option), [select_option/3]). 38:- use_module(library(dcg/basics), [string_without/4]).
{name}
. The
placeholders are replaced with corresponding values from the options
list. The result is an atom with the formatted string.
The Format string can be any atom or string containing placeholders.
The Options list should contain terms of the form name(Value)
, where
name
is the placeholder name and Value is the value to replace it
with. If a placeholder does not have a corresponding value in the
Options list, it will not be replaced, and the placeholder will remain
in the resulting atom.
84format_placeholders(Format, Atom, Options) :- 85 format_placeholders(Format, Atom, Options, _). 86 87format_placeholders(Format, Atom, Options, RestOptions) :- 88 atom_codes(Format, Codes), 89 phrase(placeholders([], Terms, Options, RestOptions), Codes), 90 must_be(ground, Terms), 91 atomic_list_concat(Terms, '', Atom).
{name}
with corresponding values from the options list. The placeholders are
replaced with the values associated with the names in the options list.
The result is a list of atoms and values, and a completed options list.
104placeholders(Terms, Options) -->
105 placeholders([], Terms, [], Options).
Scans the input, replacing placeholders of the form {name}
with
values from the options list. The result is a list of atoms and
values, and an updated options list. Uses DCG rules for flexible
parsing and substitution.
The resulting list of terms contains atoms and values, where each placeholder is replaced with the corresponding value from the options list. The options list is updated to include any new options found in the format string.
Unifies the same placeholder with the same value in the options list if it appears more than once. Placeholders can appear in the format string multiple times, and each occurrence will be replaced with the same value.
133placeholders(Terms0, Terms, Options0, Options) --> 134 "{", 135 string_without("}", NameCodes), 136 "}", 137 !, 138 { atom_codes(Name, NameCodes), 139 Option =.. [Name, Value], 140 ( option(Option, Options0) 141 -> Options_ = Options0 142 ; % Prepending the new option would be possible. 143 % See the commented-out code below. However, it is more apropos to 144 % append the new option to the end of the options list. This allows 145 % the new option to appear after any existing options that may have 146 % been specified in the Options0 list. Delegate to the merge_options/3 147 % predicate to handle the appending of the new option to the existing 148 % options list. 149 % 150 % Options_ = [Option|Options0] 151 % append(Options0, [Option], Options_) 152 merge_options([Option], Options0, Options_) 153 ), 154 append(Terms0, [Value], Terms_) 155 }, 156 placeholders(Terms_, Terms, Options_, Options). 157placeholders(Terms0, Terms, Options0, Options) --> 158 string_without("{", Codes), 159 ( { Codes == [] 160 } 161 -> { Terms = Terms0, 162 Options = Options0 163 } 164 ; { atom_codes(Atom, Codes), 165 append(Terms0, [Atom], Terms_) 166 }, 167 placeholders(Terms_, Terms, Options0, Options) 168 )
Formatting Placeholders
This module provides predicates for formatting strings with placeholders. Placeholders are specified in the form of
{name}
within a format string. The placeholders are replaced with corresponding values from a list of options, where each option is specified asname(Value)
. The result is an atom containing the formatted string. The module uses DCG rules to parse the format string and replace the placeholders with the corresponding values.The main predicate is format_placeholders/3, which takes a format string, an atom to hold the result, and a list of options. It processes the format string, replacing placeholders with their corresponding values from the options list. If a placeholder does not have a corresponding value, it will fail.
The format_placeholders/3 predicate formats a string with placeholders, while format_placeholders/4 allows for additional options to be returned; namely, the remaining options after processing the placeholders.
*/