typedKanren-0.1.0.0
Safe HaskellSafe-Inferred
LanguageHaskell2010

Kanren.Core

Description

The very core of miniKanren. So core that it basically deals with unification only. For writing relational programs, you will need Goal as well.

Synopsis

Values and terms

class Logical a where Source #

Types that can enter the relational world.

Simple types without fields, such as Bool and Int, can be used in relational programs as is. Instances for such types are as simple as

data Ternary = True | False | Maybe deriving (Eq)
instance Logical Ternary
>>> run (\x -> x === Value True)
[True]

When a type contains other types, this becomes more tricky. Consider the following type:

data Point = Point { x :: Int, y :: Int }

In the relational world, values may be known only partially. For example, we may find out that some equation is true only for a particular value of x, but once that holds, y can be anything. The definition above cannot express this, since Point has to be instantiated with some particular pair of Ints.

To account for this, we'd like to modify the definition slightly, so that each field can possibly contain a variable:

data LogicPoint = LogicPoint { logicX :: Term Int, logicY :: Term Int }

Term a here can either be a Var or a Value for type a.

Now we can specify that a Point becomes a LogicPoint in the relational world:

instance Logical Point where
  type Logic Point = LogicPoint

However, we are not finished here yet. When a type has a different representation in the logical world, we need to show how we can go from a Point to a LogicPoint with inject and go back with extract:

inject (Point x y) = LogicPoint (Value x) (Value y)
extract (LogicPoint (Value x) (Value y)) = Just (Point x y)
extract _ = Nothing

Note that while we can always transform a Point to a LogicPoint, going back to a Point can fail if any field contains a variable.

We also need to show how LogicPoints can be unified. For simple types, unification of terms works in the following way. If both terms are already known, we just check that they are equal. Otherwise, one of the terms is a variable, and we record that it must be equal to the other term.

With complex types, a third case is possible: we can refine an existing value if one of its fields is a variable. We can achieve this by unifying each field separately.

unify (LogicPoint leftX leftY) (LogicPoint rightX rightY) state =
  unify' leftX rightX state >>= unify' leftY rightY

unify takes two values being unified and the current state. If unification succeeds, a new state with acquired knowledge is returned. if unification leads to contradiction (the two values cannot be unified), unify returns Nothing. You do not modify the state yourself — this is handled by unify', a version of unify which works on Terms instead of logic values.

When we find out that a variable must have a particular value, we need not only to add a new entry in the state, but also update existing values which might contain that variable. This is the job of walk, which takes the value being updated and the current state. Just like with unify, the actual job of replacing variables with values is done by walk', and you only need to apply it to each field.

walk f (LogicPoint x y) = LogicPoint (walk' f x) (walk' f x)

You may notice that the logical representation of the type and the Logical instance are suitable for automatic generation. Indeed, the GenericLogical module provides generic versions of Logical's methods. The TH module goes further and provides makeLogic to generate logical representations for your types.

Although you'll see instances for base types below, keep in mind that they're only available from the LogicalBase module.

Minimal complete definition

Nothing

Associated Types

type Logic a = r | r -> a Source #

The logical representation of this type. This defaults to the type itself, but complex types will usually have a separate logic type.

Note that 'Logic a' is injective, so two different types cannot use the same type as their logical representation. If you want to provide an instance for newtype NT = NT T, then the logical representation should be a newtype as well: newtype LogicNT = LogicNT (Logic T).

type Logic a = a

Methods

unify :: Logic a -> Logic a -> State -> Maybe State Source #

Perform unification of two values. If unification succeeds, return the possibly modified state. If unification leads to contradiction, return Nothing.

The default implementation checks for equality, which works well for simple types. Complex types will provide their own implmentations which apply unify' to each field.

default unify :: Eq (Logic a) => Logic a -> Logic a -> State -> Maybe State Source #

walk :: State -> Logic a -> Logic a Source #

Update the value with acquired knowledge. This method the current state to substitute variables with their obtained values.

The default implementation works for simple types and returns the value as is (since there's nothing to substitute inside). Complex types will provide their own implementations which apply walk' to each field.

default walk :: a ~ Logic a => State -> Logic a -> Logic a Source #

occursCheck :: VarId b -> Logic a -> State -> Bool Source #

default occursCheck :: a ~ Logic a => VarId b -> Logic a -> State -> Bool Source #

inject :: a -> Logic a Source #

Transform a value to its logical representation.

The default implementation works for simple types and returns the value as is. Complex types will provide their own implementations which apply inject' to each field. inject' is also the function that you will use in your relational programs.

default inject :: a ~ Logic a => a -> Logic a Source #

extract :: Logic a -> Maybe a Source #

Transform a logical representation of a value back to its normal representation. Note that this transformation can fail in the general case, because variables cannot be transformed to values.

The default implementation works for simple types and returns the value as is. Complex types will provide their own implementations which apply extract' to each field. extract' is also the function that you will use in your code.

default extract :: a ~ Logic a => Logic a -> Maybe a Source #

Instances

Instances details
Logical Void Source # 
Instance details

Defined in Kanren.LogicalBase

Associated Types

type Logic Void = (r :: Type) Source #

Logical Bit Source # 
Instance details

Defined in Kanren.Data.Binary

Associated Types

type Logic Bit = (r :: Type) Source #

Logical SExpr Source # 
Instance details

Defined in Kanren.Data.Scheme

Associated Types

type Logic SExpr = (r :: Type) Source #

Logical Value Source # 
Instance details

Defined in Kanren.Data.Scheme

Associated Types

type Logic Value = (r :: Type) Source #

Logical Bool Source # 
Instance details

Defined in Kanren.LogicalBase

Associated Types

type Logic Bool = (r :: Type) Source #

Logical Char Source # 
Instance details

Defined in Kanren.LogicalBase

Associated Types

type Logic Char = (r :: Type) Source #

Logical Int Source # 
Instance details

Defined in Kanren.LogicalBase

Associated Types

type Logic Int = (r :: Type) Source #

Eq a => Logical (Atomic a) Source # 
Instance details

Defined in Kanren.Core

Associated Types

type Logic (Atomic a) = (r :: Type) Source #

Logical a => Logical (Maybe a) Source # 
Instance details

Defined in Kanren.LogicalBase

Associated Types

type Logic (Maybe a) = (r :: Type) Source #

Logical a => Logical [a] Source # 
Instance details

Defined in Kanren.LogicalBase

Associated Types

type Logic [a] = (r :: Type) Source #

Methods

unify :: Logic [a] -> Logic [a] -> State -> Maybe State Source #

walk :: State -> Logic [a] -> Logic [a] Source #

occursCheck :: VarId b -> Logic [a] -> State -> Bool Source #

inject :: [a] -> Logic [a] Source #

extract :: Logic [a] -> Maybe [a] Source #

(Logical a, Logical b) => Logical (Either a b) Source # 
Instance details

Defined in Kanren.LogicalBase

Associated Types

type Logic (Either a b) = (r :: Type) Source #

Methods

unify :: Logic (Either a b) -> Logic (Either a b) -> State -> Maybe State Source #

walk :: State -> Logic (Either a b) -> Logic (Either a b) Source #

occursCheck :: VarId b0 -> Logic (Either a b) -> State -> Bool Source #

inject :: Either a b -> Logic (Either a b) Source #

extract :: Logic (Either a b) -> Maybe (Either a b) Source #

(Logical a, Logical b) => Logical (a, b) Source # 
Instance details

Defined in Kanren.LogicalBase

Associated Types

type Logic (a, b) = (r :: Type) Source #

Methods

unify :: Logic (a, b) -> Logic (a, b) -> State -> Maybe State Source #

walk :: State -> Logic (a, b) -> Logic (a, b) Source #

occursCheck :: VarId b0 -> Logic (a, b) -> State -> Bool Source #

inject :: (a, b) -> Logic (a, b) Source #

extract :: Logic (a, b) -> Maybe (a, b) Source #

data VarId a Source #

A variable, which reserves a place for a logical value for type a.

Instances

Instances details
Show (VarId a) Source # 
Instance details

Defined in Kanren.Core

Methods

showsPrec :: Int -> VarId a -> ShowS #

show :: VarId a -> String #

showList :: [VarId a] -> ShowS #

NFData (VarId a) Source # 
Instance details

Defined in Kanren.Core

Methods

rnf :: VarId a -> () #

Eq (VarId a) Source # 
Instance details

Defined in Kanren.Core

Methods

(==) :: VarId a -> VarId a -> Bool #

(/=) :: VarId a -> VarId a -> Bool #

data Term a Source #

A logical value for type a, or a variable.

Note that a must be the “normal” type, not its logical representation, since Term stores Logic a. For example, Term (Either String (Tree Int)) will correctly use LogicList Char and LogicTree Int deep inside. This way, you do not need to know what the logic representation for a type is named, and deriving the logical representation for a type is trivial.

Constructors

Var !(VarId a) 
Value !(Logic a) 

Instances

Instances details
Generic (Term a) Source # 
Instance details

Defined in Kanren.Core

Associated Types

type Rep (Term a) :: Type -> Type #

Methods

from :: Term a -> Rep (Term a) x #

to :: Rep (Term a) x -> Term a #

IsList (Logic a) => IsList (Term a) Source # 
Instance details

Defined in Kanren.Core

Associated Types

type Item (Term a) #

Methods

fromList :: [Item (Term a)] -> Term a #

fromListN :: Int -> [Item (Term a)] -> Term a #

toList :: Term a -> [Item (Term a)] #

Num (Logic a) => Num (Term a) Source # 
Instance details

Defined in Kanren.Core

Methods

(+) :: Term a -> Term a -> Term a #

(-) :: Term a -> Term a -> Term a #

(*) :: Term a -> Term a -> Term a #

negate :: Term a -> Term a #

abs :: Term a -> Term a #

signum :: Term a -> Term a #

fromInteger :: Integer -> Term a #

Show (Logic a) => Show (Term a) Source #

This instance doesn't print the Var and Value tags. While this reduces noise in the output, this may also be confusing since fully instantiated terms may look indistinguishable from regular values.

Instance details

Defined in Kanren.Core

Methods

showsPrec :: Int -> Term a -> ShowS #

show :: Term a -> String #

showList :: [Term a] -> ShowS #

NFData (Logic a) => NFData (Term a) Source # 
Instance details

Defined in Kanren.Core

Methods

rnf :: Term a -> () #

Eq (Logic a) => Eq (Term a) Source # 
Instance details

Defined in Kanren.Core

Methods

(==) :: Term a -> Term a -> Bool #

(/=) :: Term a -> Term a -> Bool #

Logical a => Fresh (Term a) Source # 
Instance details

Defined in Kanren.Goal

Methods

fresh' :: Goal (Term a) Source #

resolve :: State -> Term a -> Term a Source #

Logical c => GLogical (K1 i c :: Type -> Type) (K1 i' (Term c) :: Type -> Type) Source # 
Instance details

Defined in Kanren.GenericLogical

Methods

gunify :: Proxy (K1 i c) -> K1 i' (Term c) p -> K1 i' (Term c) p -> State -> Maybe State

gwalk :: Proxy (K1 i c) -> State -> K1 i' (Term c) p -> K1 i' (Term c) p

goccursCheck :: Proxy (K1 i c) -> VarId b -> K1 i' (Term c) p -> State -> Bool

ginject :: K1 i c p -> K1 i' (Term c) p

gextract :: K1 i' (Term c) p -> Maybe (K1 i c p)

type Rep (Term a) Source # 
Instance details

Defined in Kanren.Core

type Rep (Term a) = D1 ('MetaData "Term" "Kanren.Core" "typedKanren-0.1.0.0-DCPxkt07imEEe1U3d5R120" 'False) (C1 ('MetaCons "Var" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VarId a))) :+: C1 ('MetaCons "Value" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Logic a))))
type Item (Term a) Source # 
Instance details

Defined in Kanren.Core

type Item (Term a) = Item (Logic a)

newtype Atomic a Source #

Treat a type as atomic, i.e. containing no variables inside. This requires a only to have an Eq instance, thus ignoring its logical representation if it exists. Useful when you really don't want to look inside something.

type Symbol = Atomic String

Constructors

Atomic a 

Instances

Instances details
Show a => Show (Atomic a) Source # 
Instance details

Defined in Kanren.Core

Methods

showsPrec :: Int -> Atomic a -> ShowS #

show :: Atomic a -> String #

showList :: [Atomic a] -> ShowS #

NFData a => NFData (Atomic a) Source # 
Instance details

Defined in Kanren.Core

Methods

rnf :: Atomic a -> () #

Eq a => Eq (Atomic a) Source # 
Instance details

Defined in Kanren.Core

Methods

(==) :: Atomic a -> Atomic a -> Bool #

(/=) :: Atomic a -> Atomic a -> Bool #

Eq a => Logical (Atomic a) Source # 
Instance details

Defined in Kanren.Core

Associated Types

type Logic (Atomic a) = (r :: Type) Source #

Eq a => Normalizable (Atomic a) Source # 
Instance details

Defined in Kanren.Core

Methods

normalize :: (forall i. VarId i -> Normalizer (VarId i)) -> Logic (Atomic a) -> Normalizer (Logic (Atomic a)) Source #

type Logic (Atomic a) Source # 
Instance details

Defined in Kanren.Core

type Logic (Atomic a) = Atomic a

Operations on terms

unify' :: Logical a => Term a -> Term a -> State -> Maybe State Source #

unify, but on Terms instead of Logic values. If new knowledge is obtained during unification, it is obtained here.

walk' :: Logical a => State -> Term a -> Term a Source #

walk, but on Terms instead of Logic values. The actual substitution of variables with values happens here.

inject' :: Logical a => a -> Term a Source #

inject, but to a Term instead of a Logic value. You will use this function in your relational programs to inject normal values.

run (\x -> x === inject' [1, 2, 3])

extract' :: Logical a => Term a -> Maybe a Source #

extract, but from a Term instead of a Logic value. Note that this transformation can fail in the general case, because variables cannot be transformed to values.

You will use this function to transform solutions of a program back to their normal representation.

>>> extract' <$> run (\x -> x === inject' (Left 42 :: Either Int Bool))
[Just (Left 42)]

class Logical a => Normalizable a where Source #

Minimal complete definition

Nothing

Methods

normalize :: (forall i. VarId i -> Normalizer (VarId i)) -> Logic a -> Normalizer (Logic a) Source #

default normalize :: a ~ Logic a => (forall i. VarId i -> Normalizer (VarId i)) -> Logic a -> Normalizer (Logic a) Source #

Instances

Instances details
Normalizable SExpr Source # 
Instance details

Defined in Kanren.Data.Scheme

Methods

normalize :: (forall i. VarId i -> Normalizer (VarId i)) -> Logic SExpr -> Normalizer (Logic SExpr) Source #

Eq a => Normalizable (Atomic a) Source # 
Instance details

Defined in Kanren.Core

Methods

normalize :: (forall i. VarId i -> Normalizer (VarId i)) -> Logic (Atomic a) -> Normalizer (Logic (Atomic a)) Source #

normalize' :: Normalizable a => (forall i. VarId i -> Normalizer (VarId i)) -> Term a -> Normalizer (Term a) Source #

Constraints

disequality :: Logical a => Term a -> Term a -> State -> Maybe State Source #

Add a constraint that two terms must not be equal.

The search state

data State Source #

One branch in the search tree. Keeps track of known substitutions and variables.

Instances

Instances details
Show State Source # 
Instance details

Defined in Kanren.Core

Methods

showsPrec :: Int -> State -> ShowS #

show :: State -> String #

showList :: [State] -> ShowS #

empty :: State Source #

The initial state without any knowledge and variables.

makeVariable :: State -> (State, Term a) Source #

Create a variable in the given state.