28

I'm trying to understand the relation between a logic programming language(Prolog in my case) and Haskell's type system.

I know both use unification and variables to find values(or types, in Haskell's type system) depending on relations. As an exercise to understand similarities and differences between them better, I tried to rewrite some simple prolog programs in Haskell's type level, but I'm having trouble with some parts.

First, I rewrote this simple prolog program:

numeral(0).
numeral(succ(X)) :- numeral(X).

add(0,Y,Y).
add(succ(X),Y,succ(Z)) :- add(X,Y,Z).

as:

class Numeral a where
    numeral :: a
    numeral = u

data Zero
data Succ a

instance Numeral Zero
instance (Numeral a) => Numeral (Succ a)

class (Numeral a, Numeral b, Numeral c) => Add a b c | b c -> a where
    add :: b -> c -> a
    add = u

instance (Numeral a) => Add a Zero a
instance (Add x y z) => Add (Succ x) (Succ y) z

it works fine, but I couldn't extend it with this Prolog:

greater_than(succ(_),0).
greater_than(succ(X),succ(Y)) :- greater_than(X,Y).

What I tried was this:

class Boolean a
data BTrue
data BFalse
instance Boolean BTrue
instance Boolean BFalse

class (Numeral a, Numeral b, Boolean r) => Greaterthan a b r | a b -> r where
    greaterthan :: a -> b -> r
    greaterthan = u

instance Greaterthan Zero Zero BFalse
instance (Numeral a) => Greaterthan (Succ a) Zero BTrue
instance (Numeral a) => Greaterthan Zero (Succ a) BFalse
instance (Greaterthan a b BTrue)  => Greaterthan (Succ a) (Succ b) BTrue
instance (Greaterthan a b BFalse) => Greaterthan (Succ a) (Succ b) BFalse

The problem with this code is that last two instances are causing fundep conflict. I can understand why, but it seems to me that it shouldn't be a problem since their guard parts(or whatever it's called it, I mean the (Greaterthan a b c) => part) are different, so that as and bs in last two insance declarations are actually different values and there are no conflicts.


Another program I tried to rewrite was this:

child(anne,bridget).
child(bridget,caroline).
child(caroline,donna).
child(donna,emily).

descend(X,Y) :- child(X,Y).
descend(X,Y) :- child(X,Z),
                descend(Z,Y).

(btw, examples are from Learn Prolog Now book)

data Anne
data Bridget
data Caroline
data Donna
data Emily

class Child a b | a -> b where
    child :: a -> b
    child = u

instance Child Anne Bridget
instance Child Bridget Caroline
instance Child Caroline Donna
instance Child Donna Emily

class Descend a b | b -> a where
    descend :: b -> a
    descend = u

instance (Child a b) => Descend a b
instance (Child a c, Descend c b) => Descend a b

And I'm getting "duplicate instances" error in last line. I think it's a similar problem, even if I have a different guard parts, I'm getting errors because body parts(I mean Descend a b parts) are the same.

So I'm looking for ways to port that Prolog programs to Haskell's type level, if possible. Any help will be appreciated.

EDIT:

Ed'ka's solution works but in a completely different way. I'm still trying to understand when we can run a Prolog program in type-system, when/why we need to write a different algorithm to make it work(like in Ed'ka's solution), and when/why there's no way to implemenet a program in Haskell's type-system.

Maybe I can find some pointers about this after reading "Fun With Functional Dependencies".

4

4 に答える 4

7

@stephen tetleyは、GHCがインスタンス宣言と一致させようとするときにすでに指摘しているように、インスタンスヘッド(=>の後のもの)のみをインスタンスコンテキスト(=>より前のもの)を完全に無視すると見なし、明確なインスタンスが見つかると、インスタンスコンテキストと一致させようとします。最初の問題のある例では、インスタンスヘッドに重複があることは明らかですが、競合する2つのインスタンスをもう1つの一般的なインスタンスに置き換えることで簡単に修正できます。

instance (Greaterthan a b r)  => Greaterthan (Succ a) (Succ b) r

ただし、2番目の例ははるかに難しいものです。Haskellで動作させるには、特定の型引数に対して特定のインスタンスが定義されているかどうかに応じて、2つの異なる結果を生成できる型レベルの関数が必要だと思います(つまり、インスタンスがある場合は、そうでない場合Child Name1 Name2は再帰的に何かを実行しName2ます) return BFalse)。これをGHCタイプでコーディングできるかどうかはわかりません(そうではないと思います)。

ただし、わずかに異なるタイプの入力に対して機能する「ソリューション」を提案できます。関係がないことを意味する代わりにparent->child(そのようなペアにインスタンスが定義されていない場合)、タイプレベルのリストを使用して既存のすべての関係を明示的にエンコードできます。次に、非常に恐れられているOverlappingInstances拡張機能Descendに依存する必要がありますが、型レベルの関数を定義できます。

{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
  FlexibleInstances, FlexibleContexts, TypeOperators,
  UndecidableInstances, OverlappingInstances #-}

data Anne
data Bridget
data Caroline
data Donna
data Emily
data Fred
data George

-- Type-level list
data Nil
infixr 5 :::
data x ::: xs

-- `bs` are children of `a`
class Children a bs | a -> bs

instance Children Anne (Bridget ::: Nil)
instance Children Bridget (Caroline ::: Donna ::: Nil)
instance Children Caroline (Emily ::: Nil)
-- Note that we have to specify children list for everyone
-- (`Nil` instead of missing instance declaration)
instance Children Donna Nil
instance Children Emily Nil
instance Children Fred (George ::: Nil)
instance Children George Nil

-- `or` operation for type-level booleans 
class OR a b bool | a b -> bool
instance OR BTrue b BTrue
instance OR BFalse BTrue BTrue
instance OR BFalse BFalse BFalse

-- Is `a` a descendant of `b`?
class Descend  a b bool | a b -> bool
instance (Children b cs, PathExists cs a r) => Descend a b r

-- auxiliary function which checks if there is a transitive relation
-- to `to` using all possible paths passing `children`
class PathExists children to bool | children to -> bool

instance PathExists Nil a BFalse
instance PathExists (c ::: cs) c BTrue
instance (PathExists cs a r1, Children c cs1, PathExists cs1 a r2, OR r1 r2 r)
    => PathExists (c ::: cs) a r

-- Some tests
instance Show BTrue where
    show _ = "BTrue"

instance Show BFalse where
    show _ = "BFalse"

t1 :: Descend Donna Anne r => r
t1 = undefined -- outputs `BTrue`

t2 :: Descend Fred Anne r => r
t2 = undefined -- outputs `BFalse`

OverlappingInstancesの2番目と3番目のインスタンスはPathExistsどちらも空のリストではない場合に一致する可能性があるため、ここで必要ですが、GHCは、リストの先頭が引数childrenと等しいかどうかに応じて、より具体的なものを決定できます(そうである場合は、toパス、つまり子孫)。

于 2012-12-17T04:01:23.860 に答える
6

As for the GreaterThan example, I don't see how introducing those Booleans is a step faithful to the original Prolog code. It seems you are trying to encode a sense of decidability in your Haskell version that is not present in the Prolog version.

So all in all, you can just do

{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
class Numeral a where

data Zero
data Succ a

instance Numeral Zero
instance (Numeral a) => Numeral (Succ a)

class (Numeral a, Numeral b) => Greaterthan a b where

instance (Numeral a) => Greaterthan Zero (Succ a)
instance (Greaterthan a b)  => Greaterthan (Succ a) (Succ b)

Actually with data kinds, you can write it nicer (but I can't try it now, as I only have ghc 7.2 installed here):

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}

data Numeral = Zero | Succ Numeral

class Greaterthan (a :: Numeral) (b :: Numeral) where

instance Greaterthan Zero (Succ a)
instance (Greaterthan a b)  => Greaterthan (Succ a) (Succ b)
于 2012-12-17T04:02:10.620 に答える
2

For Ed'ka solution you could use:

import Data.HList.TypeCastGeneric2
instance TypeCast nil Nil => Children a nil

instead of one instance for each person who has no children.

于 2012-12-17T04:25:19.453 に答える
0

I've played around with the second problem, and here is what I found out. It is possible to formulate the problem "a-la" Prolog, but some caveats apply. One of those caveats is that Descend doesn't actually have any functional dependencies between arguments, it's a binary predicate, not a unary function.

To begin with, let me show the code:

{-# LANGUAGE FunctionalDependencies
           , FlexibleInstances
           , UndecidableInstances
           , NoImplicitPrelude
           , AllowAmbiguousTypes
           #-}

data Anne
data Bridget
data Caroline
data Donna
data Emily

class Child a b | a -> b

instance Child Anne Bridget
instance Child Bridget Caroline
instance Child Caroline Donna
instance Child Donna Emily

----------------------------------------------------

data True -- just for nice output

class Descend a b where descend :: True

instance {-# OVERLAPPING #-} Descend a a
instance (Child a b, Descend b c) => Descend a c

(you can test this in GHCi by enabling :set -XTypeApplications and running something like :t descend @Anne @Caroline and :t descend @Caroline @Anne)

So, this mostly follows the Prolog example, with one important difference: instead of descend(X,Y) :- child(X,Y) we have

instance {-# OVERLAPS #-} Descend a a

I will explain momentarily why that is, but first I will explain what it changes: basically, the Descend relation becomes reflective, i.e. Descend a a is true for all a. This is not the case with the Prolog example, where the recursion terminates one step earlier.

Now for why that is. Consider how GHC implements type variable substitutions during type instance resolution: it matches the instance head, unifying the type variables, then checks the instance constraints. Hence, for example, Descend Anne Caroline will be resolved with the following sequence:

  1. First Descend Anne Caroline is matched against Descend a c, conveniently a=Anne, c=Caroline
  2. Hence, we look up instances Child Anne b and Descend b Caroline.
  3. Generally, GHC would give up here since it wouldn't know what b means. But since in Child b is functionally dependent on a, Child Anne b is resolved to Child Anne Bridget, hence b=Bridget, and we try to resolve Descend Bridget Caroline.
  4. Descend Bridget Caroline is again matched against Descend a c, a=Bridget, c is yet again Caroline.
  5. Lookup Child Bridget b, which resolves to Child Bridget Caroline. Then try to resolve Descend Caroline Caroline.
  6. Descend Caroline Caroline is matched with overlapping instance Descend a a and the process terminates.

So, GHC actually can't stop iterating early due to how instances are matched.

That said, if we replace Child with a closed type family, it becomes workable:

{-# LANGUAGE TypeFamilies
           , FunctionalDependencies
           , FlexibleInstances
           , UndecidableInstances
           , TypeOperators
           , NoImplicitPrelude
           , AllowAmbiguousTypes
           , ScopedTypeVariables
           #-}

data Anne
data Bridget
data Caroline
data Donna
data Emily

data True
data False

type family Child' a where
 Child' Anne     = Bridget
 Child' Bridget  = Caroline
 Child' Caroline = Donna
 Child' Donna    = Emily
 Child' a        = False

class Child a b | a -> b

instance (Child' a ~ b) => Child a b

----------------------------------------------------

class Descend' a b flag
class Descend a b where descend :: True

data Direct
data Indirect

type family F a b where
  F False a = Direct
  F a a = Direct
  F a b = Indirect

instance (Child' a ~ c) => Descend' a c Direct
instance (Child a b, Descend' b c (F (Child' b) c))
  => Descend' a c Indirect
instance (Descend' a b (F (Child' a) b))
  => Descend a b

The dance with Descend' is just to be able to overload instance selection based on context, as described in https://wiki.haskell.org/GHC/AdvancedOverlap. The main difference is we can apply Child' several times in order to "look ahead".

于 2021-03-09T16:18:32.547 に答える