Prolog 中的算术,使用 2 的幂表示数字

2024-01-08

我有两个数字,让我们命名它们N and K,我想写N using K2 的幂。

例如如果N = 9 and K = 4, then N可能N = 1 + 2 + 2 + 4 (2^0 + 2^1 + 2^1 + 2^2).

我的程序应该输出类似的内容N = [1,2,2,4].

我习惯了C++。我在Prolog中找不到解决这个问题的方法。任何帮助将不胜感激!


我认为这将是使用 CLP(FD) 的几行,但没有骰子。可以做得更简单吗?

所以这是完整的解决方案。

不要以为我是一次性想出这个方法的,其中有一些迭代和死胡同。

:- use_module(library(debug)).

% ---
% powersum(+N,+Target,?Solution)
% ---
% Entry point. Relate a list "Solution" of "N" integers to the integer
% "Target", which is the sum of 2^Solution[i].
% This works only in the "functional" direction
% "Compute Solution as powersum(N,Target)"
% or the "verification" direction
% "is Solution a solution of powersum(N,Target)"?
%
% An extension of some interest would be to NOT have a fixed "N".
% Let powersum/2 find appropriate N.
%
% The search is subject to exponential slowdown as the list length
% increases, so one gets bogged down quickly.
% ---

powersum(N,Target,Solution) :- 
   ((integer(N),N>0,integer(Target),Target>=1) -> true ; throw("Bad args!")),   
   length(RS,N),                             % create a list RN of N fresh variables
   MaxPower is floor(log(Target)/log(2)),    % that's the largest power we will find in the solution
   propose(RS,MaxPower,Target,0),            % generate & test a solution into RS
   reverse(RS,Solution),                     % if we are here, we found something! Reverse RS so that it is increasing
   my_write(Solution,String,Value),          % prettyprinting
   format("~s = ~d\n",[String,Value]).

% ---
% propose(ListForSolution,MaxPowerHere,Target,SumSoFar)
% ---
% This is an integrate "generate-and-test". It is integrated
% to "fail fast" during proposal - we don't want to propose a
% complete solution, then compute the value for that solution 
% and find out that we overshot the target. If we overshoot, we
% want to find ozut immediately!
%
% So: Propose a new value for the leftmost position L of the 
% solution list. We are allowed to propose any integer for L 
% from the sequence [MaxPowerHere,...,0]. "Target" is the target
% value we must not overshoot (indeed, we which must meet
% exactly at the end of recursion). "SumSoFar" is the sum of
% powers "to our left" in the solution list, to which we already
% committed.

propose([L|Ls],MaxPowerHere,Target,SumSoFar) :- 
   assertion(SumSoFar=<Target),
   (SumSoFar=Target -> false ; true),          % a slight optimization, no solution if we already reached Target!
   propose_value(L,MaxPowerHere),              % Generate: L is now (backtrackably) some value from [MaxPowerHere,...,0]
   NewSum is (SumSoFar + 2**L),                
   NewSum =< Target,                           % Test; if this fails, we backtrack to propose_value/2 and will be back with a next L
   NewMaxPowerHere = L,                        % Test passed; the next power in the sequence should be no larger than the current, i.e. L
   propose(Ls,NewMaxPowerHere,Target,NewSum).  % Recurse over rest-of-list.

propose([],_,Target,Target).                   % Terminal test: Only succeed if all values set and the Sum is the Target!

% ---
% propose_value(?X,+Max).
% ---
% Give me a new value X between [Max,0].
% Backtracks over monotonically decreasing integers.
% See the test code for examples.
%
% One could also construct a list of integers [Max,...,0], then
% use "member/2" for backtracking. This would "concretize" the predicate's
% behaviour with an explicit list structure.
%
% "between/3" sadly only generates increasing sequences otherwise one
% could use that. Maybe there is a "between/4" taking a step value somewhere?
% ---

propose_value(X,Max) :- 
   assertion((integer(Max),Max>=0)),
   Max=X.
propose_value(X,Max) :- 
   assertion((integer(Max),Max>=0)),
   Max>0, succ(NewMax,Max), 
   propose_value(X,NewMax).

% ---
% I like some nice output, so generate a string representing the solution.
% Also, recompute the value to make doubly sure!
% ---

my_write([L|Ls],String,Value) :-
   my_write(Ls,StringOnTheRight,ValueOnTheRight),
   Value is ValueOnTheRight + 2**L,
   with_output_to(string(String),format("2^~d + ~s",[L,StringOnTheRight])).

my_write([L],String,Value) :-
   with_output_to(string(String),format("2^~d",[L])),
   Value is 2**L.



:- begin_tests(powersum).

% powersum(N,Target,Solution) 

test(pv1)       :- bagof(X,propose_value(X,3),Bag), Bag = [3,2,1,0].
test(pv2)       :- bagof(X,propose_value(X,2),Bag), Bag = [2,1,0].
test(pv2)       :- bagof(X,propose_value(X,1),Bag), Bag = [1,0].
test(pv3)       :- bagof(X,propose_value(X,0),Bag), Bag = [0].

test(one)       :- bagof(S,powersum(1,1,S),Bag), Bag = [[0]].
test(two)       :- bagof(S,powersum(3,10,S),Bag), Bag = [[0,0,3],[1,2,2]].
test(three)     :- bagof(S,powersum(3,145,S),Bag), Bag = [[0,4,7]].
test(four,fail) :- powersum(3,8457894,_).
test(five)      :- bagof(S,powersum(9,8457894,S), Bag), Bag = [[1, 2, 5, 7, 9, 10, 11, 16, 23]]. %% VERY SLOW

:- end_tests(powersum).

rt :- run_tests(powersum).

由于最后一个单元测试线运行了 2 分钟的测试...

?- time(rt).
% PL-Unit: powersum ....2^0 = 1
.2^0 + 2^0 + 2^3 = 10
2^1 + 2^2 + 2^2 = 10
.2^0 + 2^4 + 2^7 = 145
..2^1 + 2^2 + 2^5 + 2^7 + 2^9 + 2^10 + 2^11 + 2^16 + 2^23 = 8457894
. done
% All 9 tests passed
% 455,205,628 inferences, 114.614 CPU in 115.470 seconds (99% CPU, 3971641 Lips)
true.
本文内容由网友自发贡献,版权归原作者所有,本站不承担相应法律责任。如您发现有涉嫌抄袭侵权的内容,请联系:hwhale#tublm.com(使用前将#替换为@)

Prolog 中的算术,使用 2 的幂表示数字 的相关文章

  • prolog中输入/输出参数的区别

    Prolog谓词定义中的输入和输出参数有什么区别吗 这与其他语言 例如Scheme 和C 相比如何 我希望我理解你的问题 您应该研究一下 Prolog 中如何实现统一 因为它会让事情变得更清晰 反正 简而言之 没有内置方法可以将 Prolo
  • 在序言中返回列表

    我想问一个关于返回列表的问题 事实 团队 团队名称 总监 国籍 总体目标 team milan allegri italy 8 5 team inter benitez italy 7 6 team barcelona guardiola
  • 如何在SWI-Prolog中启用所有统一中的发生检查?

    根据维基百科 https en wikipedia org wiki Occurs check 为所有统一提供声音统一的实现是 Qu Prolog 和 Strawberry Prolog 以及 可选地 通过运行时标志 XSB SWI Pro
  • 从序言中的列表中过滤掉大量数字

    我想编写一个函数 通过删除所有小于或等于特定数字的内容来过滤数字列表 该函数将采用两个参数 数字列表和要过滤的数字 该函数应返回一个列表 其中包含大于过滤器编号的所有数字 有时像这样 filter num list L1 N L2 test
  • 如何确定矩阵的所有给定坐标都是相连的?

    给定一个网格 我如何确定网格的元素是否都在单个区域中 在下面的情况下是正确的 因为矩阵中的每个元素都有一个邻居 示例1 gridneighbours 1 1 1 2 1 3 2 1 2 2 2 3 3 1 4 1 4 2 true 然而在我
  • 如何在 Prolog 中修复这个循环谓词?

    为什么这不能在 Prolog 中定义 已婚 married X Y married Y X 这些类型的循环谓词不允许吗 我该如何解决它 Thanks 如果我的语法错误请原谅我 我已经有一段时间没有使用 Prolog 了 典型的解决方案是在子
  • Prolog 中的失败谓词有什么用?

    我想不出我需要它的情况 优雅的系统提供false 0作为命令式的声明式同义词fail 0 它有用的一个例子是当您想要手动强制回溯副作用时 例如 between 1 3 N format line w n N false line 1 lin
  • Prolog 中的掩码

    我最近一直在尝试理解 Prolog 并且一直在搞乱 Prolog 中的列表列表 我正在尝试创建一种我想在 p 中的面具 序言 我有一个谓词 它确定 Prolog 中两个列表列表 比如说 L1 和 L2 之间的差异 并将它们保存为列表列表 比
  • Prolog 时间重叠问题

    假设我有这个知识库 free ann slot time 8 0 time 9 0 free ann slot time 10 0 time 11 0 free bob slot time 7 0 time 8 30 free bob sl
  • Prolog:消除查询中的重复

    我一直在尝试编写一个简单的代码 其行为方式如下 hasCoppiesOf X a b a b a b a b X a b X a b a b X a b a b a b a b And hasCoppiesOf a b a b a b a
  • 编写 Prolog 谓词的最佳实践是什么,以便它以指定参数的不同方式工作

    我正在尝试实现一些简单的谓词 例如 my length 或 my append 如果我们事先知道我们想要找到列表的长度 或者我们想要附加两个列表 这对我来说很容易 即我知道什么是输入 什么是输出 在 Prolog 中 可以用其他方式做事 如
  • Prolog - 递归列表构建

    对于我正在编写的程序 我需要创建一个列表列表 其中包含代表乘积的数字对和两个给定数字的总和 现在我有一个函数 我可以指定将列表添加到列表中的次数 稍后将使用完整功能进行扩展 这是我所拥有的 s1 0 X s1 Q X N is Q 1 mu
  • 在 Prolog 中编辑 Eliza 聊天机器人

    我一直在努力尝试在 Prolog 中编辑 Eliza 聊天机器人 每次我尝试编辑某些内容时 都会出现新的错误 它是否受到任何形式的编辑保护 我使用 SWI prolog 编辑器进行编辑 问题是我试图在没有完全理解代码的情况下最小化代码 我正
  • 如何使用 Prolog 查找二叉树的深度

    我正在学习 Prolog 并试图找到一个深度二叉树使用 Prolog 我代表一棵树是这样的 nil is a tree tree 1 nil nil this is a leaf tree 1 tree 1 nil nil nil this
  • 关于构建列表直至满足条件

    我想解决 巨猫军团之谜 https youtu be YeMVoJKn1Tg由 Dan Finkel 使用 Prolog 编写 基本上你从 0 然后使用以下三个操作之一构建此列表 添加5 添加7 或采取sqrt 当您成功建立一个列表后 您就
  • 硬币兑换 DP 解决方案以跟踪硬币

    尝试为一般的硬币找零问题编写一个 DP 解决方案 该解决方案还可以跟踪使用了哪些硬币 到目前为止 我已经可以为我提供所需的最低数量的硬币 但无法弄清楚如何获取使用了哪些硬币以及使用了多少次 如果使用硬币 我尝试设置另一个带有值的表 布尔值
  • 执行树元解释

    我有根据我之前的问题制作的跟踪元解释器here https stackoverflow com questions 27235148 implementing cut in tracing meta interpreter prolog 我
  • 在 prolog 中读取用户输入的字符串

    我是 Prolog 初学者 我正在使用 swi prolog 刚刚开始使用它 我需要将用户输入字符串拆分到列表中 我尝试了以下代码 但出现错误 指出 在子句正文中完全停止 无法重新定义 2 write Enter the String nl
  • 列表中的连续元素

    我正在阻止一个谓词来编码Prolog 我需要对两个谓词进行编码 如果我打电话 u a b c d e f X 它会给X a b X b c X c d 如果我打电话 v a b c d e f X 它会给X a b X c d X e f
  • Prolog内存问题

    我想找到一种方法来分析我在序言中编写的谓词 一个巨大的谓词 的内存使用情况 我目前正在运行它swi http www swi prolog org and yap http www dcc fc up pt vsc Yap document

随机推荐

  • 使用 SynchronizationContext 将事件发送回 WinForms 或 WPF 的 UI

    我使用 SynchronizationContext 将事件从执行大量多线程后台任务的 DLL 封送回 UI 线程 我知道单例模式不是我最喜欢的 但是当您创建 foo 的父对象时 我现在使用它来存储 UI 的 Synchronization
  • 获取存储为字符的时间变量的时间差

    我的数据框中有两个字符变量start time and stop time start time stop time
  • jQuery flot 并排多条形图

    我使用 jQuery 绘图和类别插件来创建图表 我想使用以下代码并排绘制每个月的两个条形图 plot chart label Neue Mitglieder data data order 1 label F llige K ndigung
  • 如何在eclipse中过滤消息到Logcat?

    我只想从当前运行的应用程序向 logcat 显示 system out println 消息 我已经检查了堆栈溢出和其他人的许多建议 但我得到的只是像 add adb d logcat com example example I S 等等
  • BeginProcessRequest() 中会发生什么?

    我们使用 NewRelic 来提供服务器端应用程序跟踪 我们注意到 我们的一些应用程序在该方法中始终花费大约 100 毫秒System Web Mvc MvcHandler BeginProcessRequest 这种情况发生在调用任何自定
  • ViewScoped Bean 内 SessionScope 的 ManagedProperty - 瞬态?

    我有这样的 JSF Beans 结构 ManagedBean ViewScoped public class ViewBeany implements Serializable ManagedProperty value sessionBe
  • C# 类型转换:存在显式强制转换但引发转换错误?

    我了解到HashSet实施IEnumerable界面 因此 可以隐式地强制转换HashSet对象进入IEnumerable HashSet
  • Flutter - 拖动标记并获得新位置

    在 Flutter 中 我有一张地图 可以在以下帮助下获取设备位置location https pub dartlang org packages location 然后我使用这个位置在 Google 地图中显示标记谷歌地图颤振 https
  • 在 JSON-LD 中,是否可以为属性值定义 URI 映射?

    假设我们有以下 JSON context name http schema org name status http schema org status name Manu Sporny status trollin The trollin
  • 有没有 Runtime.getRuntime().exec() 的替代方法

    只是想知道 是否有比这更好 更新 更安全 更快等的东西Runtime getRuntime exec 我想在 Linux 上从我的应用程序运行另一个进程 这是我知道的唯一方法 如果有替代方案就好了 怎么样流程构建器 http downloa
  • Sublime Text 3 中的自定义语法

    我正在努力找出如何使用新的 Sublime Text 3 创建新的语法突出显示 sublime 语法风格定义 之前的大多数答案都与旧的做法有关 从 Sublime Text Build 3084 开始 添加了新的语法定义格式 扩展名为 su
  • ASP.NET 主题未正确呈现

    我有一个使用主题的小型网络应用程序 主题在主机上工作 因此在预初始化时 如果主机 a 则加载 x 主题 如果主机 b 则加载 y 主题 在我的代码中 这看起来像 如果 request url host contains a 那么 页面 主题
  • ios 8.4.1 webview黑屏

    我需要在 ios 中在一个简单的 webview 中创建一个应用程序 我用example https github com vandadnp iOS 8 Swift Programming Cookbook blob master chap
  • 在日志传送的辅助服务器上创建用户

    我有一个生产服务器说ServerA我已设置日志传送到ServerB其处于只读模式 此日志传送的目的是降低生产服务器上某些昂贵的查询 痛苦的报告 的负载 现在 如果我必须使用我们的域帐户创建一些登录名 我无法执行此操作 因为辅助数据库位于st
  • 如何从 Rust 中的 Vec 中提取两个可变元素[重复]

    这个问题在这里已经有答案了 我试图从 Vec 中提取两个元素 它始终包含至少两个元素 这两个元素需要可变地提取 因为我需要能够在单个操作中更改这两个元素的值 示例代码 struct Piece x u32 y u32 name static
  • 使用 CSS 将按钮放置在另一个按钮之上

    我在这里需要一些高级 CSS 帮助 我有一个登录按钮和一个注册按钮 我只想一次显示一个 如果用户未登录 注册按钮应出现在登录按钮的顶部 我们有一个复杂而疯狂的后端 如果服务器认为用户未登录 它将生成注册按钮的代码 但是两者都会由服务器输出
  • Windows Python:使用区域设置模块更改编码

    使用Python 2 7 我正在编写一个抽象的网络抓取工具 在显示 打印 某些字符时遇到问题 我收到回溯错误 UnicodeEncodeError ascii codec can t encode character u u2606 in
  • 什么是无符号字符?

    在 C C 中 什么是unsigned char是用来 和普通的有什么不同char 在C 中 有以下三种distinct字符类型 char signed char unsigned char 1 char 如果您使用字符类型text 使用不
  • 如何从组件模板将数组作为 Input() 传递?

    我需要使用绑定将值数组传递给组件 例如 Component selector my component template div div export class MyComponent Input data any 然而 Angular
  • Prolog 中的算术,使用 2 的幂表示数字

    我有两个数字 让我们命名它们N and K 我想写N using K2 的幂 例如如果N 9 and K 4 then N可能N 1 2 2 4 2 0 2 1 2 1 2 2 我的程序应该输出类似的内容N 1 2 2 4 我习惯了C 我在