typedKanren-0.1.0.0
Safe HaskellSafe-Inferred
LanguageHaskell2010

Kanren.LogicalBase

Description

Logical representations for some base types along with their (orphan) Logical instances.

Synopsis

Primitive types

There are Logical instances for Bool, Char, Int, and Void. They don't require a separate logic representation.

Prisms for Bool

_False' :: ExhaustivePrism Bool (false, true) (false', true) () false false' Source #

_True' :: ExhaustivePrism Bool (false, true) (false, true') () true true' Source #

Tuples

For tuples, the logical representation is a tuple too, so they don't need a separate logic type. Currently, there's a Logical instance for 2-tuples only.

Lists

data LogicList a Source #

Constructors

LogicNil 
LogicCons (Term a) (Term [a]) 

Instances

Instances details
Generic (LogicList a) Source # 
Instance details

Defined in Kanren.LogicalBase

Associated Types

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

Methods

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

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

IsList (LogicList a) Source # 
Instance details

Defined in Kanren.LogicalBase

Associated Types

type Item (LogicList a) #

Methods

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

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

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

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

This instance tries to print the list as a regular one. In case the tail is unknown, the list is printed as [...|_.n], like in Prolog.

Instance details

Defined in Kanren.LogicalBase

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

Defined in Kanren.LogicalBase

Methods

rnf :: LogicList a -> () #

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

Defined in Kanren.LogicalBase

Methods

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

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

type Rep (LogicList a) Source # 
Instance details

Defined in Kanren.LogicalBase

type Rep (LogicList a) = D1 ('MetaData "LogicList" "Kanren.LogicalBase" "typedKanren-0.1.0.0-DCPxkt07imEEe1U3d5R120" 'False) (C1 ('MetaCons "LogicNil" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LogicCons" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term [a]))))
type Item (LogicList a) Source # 
Instance details

Defined in Kanren.LogicalBase

type Item (LogicList a) = Term a

Prisms for lists

_LogicNil :: forall a. Prism' (LogicList a) () Source #

_LogicCons :: forall a a. Prism (LogicList a) (LogicList a) (Term a, Term [a]) (Term a, Term [a]) Source #

_LogicNil' :: ExhaustivePrism (LogicList a) (logicNil, logicCons) (logicNil', logicCons) () logicNil logicNil' Source #

_LogicCons' :: ExhaustivePrism (LogicList a) (logicNil, logicCons) (logicNil, logicCons') (Term a, Term [a]) logicCons logicCons' Source #

Maybe

data LogicMaybe (a :: Type) Source #

Constructors

LogicNothing 
LogicJust (Term a) 

Instances

Instances details
Generic (LogicMaybe a) Source # 
Instance details

Defined in Kanren.LogicalBase

Associated Types

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

Methods

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

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

Show (Logic a) => Show (LogicMaybe a) Source # 
Instance details

Defined in Kanren.LogicalBase

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

Defined in Kanren.LogicalBase

Methods

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

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

type Rep (LogicMaybe a) Source # 
Instance details

Defined in Kanren.LogicalBase

type Rep (LogicMaybe a) = D1 ('MetaData "LogicMaybe" "Kanren.LogicalBase" "typedKanren-0.1.0.0-DCPxkt07imEEe1U3d5R120" 'False) (C1 ('MetaCons "LogicNothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LogicJust" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term a))))

Prisms for Maybe

_LogicNothing :: forall a. Prism' (LogicMaybe a) () Source #

_LogicJust :: forall a a. Prism (LogicMaybe a) (LogicMaybe a) (Term a) (Term a) Source #

_LogicNothing' :: ExhaustivePrism (LogicMaybe a) (logicNothing, logicJust) (logicNothing', logicJust) () logicNothing logicNothing' Source #

_LogicJust' :: ExhaustivePrism (LogicMaybe a) (logicNothing, logicJust) (logicNothing, logicJust') (Term a) logicJust logicJust' Source #

Either

data LogicEither (a :: Type) (b :: Type) Source #

Constructors

LogicLeft (Term a) 
LogicRight (Term b) 

Instances

Instances details
Generic (LogicEither a b) Source # 
Instance details

Defined in Kanren.LogicalBase

Associated Types

type Rep (LogicEither a b) :: Type -> Type #

Methods

from :: LogicEither a b -> Rep (LogicEither a b) x #

to :: Rep (LogicEither a b) x -> LogicEither a b #

(Show (Logic a), Show (Logic b)) => Show (LogicEither a b) Source # 
Instance details

Defined in Kanren.LogicalBase

Methods

showsPrec :: Int -> LogicEither a b -> ShowS #

show :: LogicEither a b -> String #

showList :: [LogicEither a b] -> ShowS #

(Eq (Logic a), Eq (Logic b)) => Eq (LogicEither a b) Source # 
Instance details

Defined in Kanren.LogicalBase

Methods

(==) :: LogicEither a b -> LogicEither a b -> Bool #

(/=) :: LogicEither a b -> LogicEither a b -> Bool #

type Rep (LogicEither a b) Source # 
Instance details

Defined in Kanren.LogicalBase

type Rep (LogicEither a b) = D1 ('MetaData "LogicEither" "Kanren.LogicalBase" "typedKanren-0.1.0.0-DCPxkt07imEEe1U3d5R120" 'False) (C1 ('MetaCons "LogicLeft" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term a))) :+: C1 ('MetaCons "LogicRight" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term b))))

Prisms for Either

_LogicLeft :: forall a b a. Prism (LogicEither a b) (LogicEither a b) (Term a) (Term a) Source #

_LogicRight :: forall a b b. Prism (LogicEither a b) (LogicEither a b) (Term b) (Term b) Source #

_LogicLeft' :: ExhaustivePrism (LogicEither a b) (logicLeft, logicRight) (logicLeft', logicRight) (Term a) logicLeft logicLeft' Source #

_LogicRight' :: ExhaustivePrism (LogicEither a b) (logicLeft, logicRight) (logicLeft, logicRight') (Term b) logicRight logicRight' Source #

Orphan instances

Logical Void Source # 
Instance details

Associated Types

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

Logical Bool Source # 
Instance details

Associated Types

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

Logical Char Source # 
Instance details

Associated Types

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

Logical Int Source # 
Instance details

Associated Types

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

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

Associated Types

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

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

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

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

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 #