opencog-atomspace-0.1.0.0: Haskell Bindings for the AtomSpace.

Safe HaskellNone
LanguageHaskell98

OpenCog.AtomSpace

Contents

Description

This library defines Haskell Bindings for the AtomSpace.

Synopsis

AtomSpace Environment

data AtomSpace a Source

Main Data Type for representing programs working on an AtomSpace.

Note that AtomSpace is an instance of the type class: MonadIO

(We have to use the IO monad because of the use of FFI for calling c functions for working on a mutable instance of the atomspace, so we have side effects).

So, you can lift IO actions inside the monad AtomSpace, through the use of liftIO.

data AtomSpaceObj Source

AtomSpaceObj is a specific AtomSpace instance.

getParent :: AtomSpaceObj -> Maybe AtomSpaceObj Source

getParent given an AtomSpace instance returns the parent AtomSpace.

newAtomSpace :: Maybe AtomSpaceObj -> IO AtomSpaceObj Source

newAtomSpace creates a new Atomspace, from a optionally given parent atomspace.

onAtomSpace :: AtomSpaceObj -> AtomSpace a -> IO a Source

onAtomSpace runs the specified computation on the atomspace instance provided.

(<:) :: AtomSpaceObj -> AtomSpace a -> IO a infixr 0 Source

Syntactic sugar for calling the function onAtomSpace. For example, we can write code like this:

main :: IO ()
main = do
   parentAS <- newAtomSpace Nothing
   childAS <- newAtomSpace (Just parentAS)

   parentAS <: insert (ConceptNode GenConcept noTv)
   childAS  <: do
       insert (ConceptNode PrivateConcept1 (stv 1 1))
       insert (ConceptNode PrivateConcept2 (stv 0.5 1))
   parentAS <: program
   childAS  <: debug
   parentAS <: remove (ConceptNode GenConcept noTv)

program :: AtomSpace ()
program = do
    s <- get (ConceptNode GenConcept noTv)
    ...

runOnNewAtomSpace :: AtomSpace a -> IO a Source

runOnNewAtomSpace creates a new AtomSpace (C++ object) and does some computation over it.

AtomSpace Interaction

insert :: Typeable a => Atom a -> AtomSpace () Source

insert creates a new atom on the atomspace or updates the existing one.

remove :: Typeable a => Atom a -> AtomSpace Bool Source

remove deletes an atom from the atomspace. Returns True in success or False if it couldn't locate the specified atom.

get :: a <~ AtomT => Atom a -> AtomSpace (Maybe (Atom a)) Source

get looks for an atom in the atomspace and returns it. (With updated mutable information)

debug :: AtomSpace () Source

debug prints the state of the AtomSpace on stderr. (only for debugging purposes)

AtomSpace Query

cogBind :: Atom BindT -> AtomSpace (Maybe AtomGen) Source

cogBind calls the pattern matcher with the given bindLink. (you should insert the bindlink to the atomspace before using this function).

AtomSpace Printing

printAtom :: Typeable a => Atom a -> IO () Source

printAtom prints the given atom on stdout.

showAtom :: Typeable a => Atom a -> String Source

showAtom shows an atom in opencog notation (indented notation).

AtomSpace Main Data Types

data TruthVal Source

TruthVal represent the different types of TruthValues.

Instances

type AtomName = String Source

Atom name type.

data Atom a where Source

Atom is the main data type to represent the different types of atoms.

Here we impose type constraints in how atoms relate between them.

The <~ type operator means that the type on the left "inherits" from the type on the right.

DEFINING NEW ATOM TYPES:

  • If it is a node:

    We add a new data constructor such as:

     NewAtomTypeNode :: AtomName -> TVal -> Atom NewAtomTypeT

    where NewAtomTypeT is a phantom type (automatically generated by temp. hask.).

  • If it is a link:
    • If it is of a fixed arity:

      We impose the type constraints on each of the members of its outgoing set.

       NewAtomTypeLink :: (a t1,b <~ t2,c <~ t3) =
                 TVal -> Atom a -> Atom b -> Atom c -> AtomNewAtomTypeT
    • If it is of unlimited arity:

      We define it as a data constructor that takes a list of atoms as first argument. All the members of its outgoing set will satisfy the same constraints.

      For example suppose NewAtomTypeLink accepts nodes that are concepts:

       NewAtomTypeLink :: TVal -> [Gen ConceptT] -> Atom NewAtomTypeT

Also, you have to modify the module Internal. Adding proper case clauses for this new atom type to the functions "toRaw" and "fromRaw".

Constructors

PredicateNode :: AtomName -> TVal -> Atom PredicateT 
AndLink :: TVal -> [AtomGen] -> Atom AndT 
OrLink :: TVal -> [AtomGen] -> Atom OrT 
ImplicationLink :: (a <~ AtomT, b <~ AtomT) => TVal -> Atom a -> Atom b -> Atom ImplicationT 
EquivalenceLink :: (a <~ AtomT, b <~ AtomT) => TVal -> Atom a -> Atom b -> Atom EquivalenceT 
EvaluationLink :: (p <~ PredicateT, l <~ ListT) => TVal -> Atom p -> Atom l -> Atom EvaluationT 
ConceptNode :: AtomName -> TVal -> Atom ConceptT 
InheritanceLink :: (c1 <~ ConceptT, c2 <~ ConceptT) => TVal -> Atom c1 -> Atom c2 -> Atom InheritanceT 
SimilarityLink :: (c1 <~ ConceptT, c2 <~ ConceptT) => TVal -> Atom c1 -> Atom c2 -> Atom SimilarityT 
MemberLink :: (c1 <~ NodeT, c2 <~ NodeT) => TVal -> Atom c1 -> Atom c2 -> Atom MemberT 
SatisfyingSetLink :: p <~ PredicateT => Atom p -> Atom SatisfyingSetT 
NumberNode :: Double -> Atom NumberT 
ListLink :: [AtomGen] -> Atom ListT 
SetLink :: [AtomGen] -> Atom SetT 
SchemaNode :: AtomName -> Atom SchemaT 
GroundedSchemaNode :: AtomName -> Atom GroundedSchemaT 
ExecutionLink :: (s <~ SchemaT, l <~ ListT, a <~ AtomT) => Atom s -> Atom l -> Atom a -> Atom ExecutionT 
VariableNode :: AtomName -> Atom VariableT 
VariableList :: [Gen VariableT] -> Atom VariableT 
SatisfactionLink :: (v <~ VariableT, l <~ LinkT) => Atom v -> Atom l -> Atom SatisfactionT 
ForAllLink :: (v <~ ListT, i <~ ImplicationT) => TVal -> Atom v -> Atom i -> Atom ForAllT 
AverageLink :: (v <~ VariableT, a <~ AtomT) => TVal -> Atom v -> Atom a -> Atom AverageT 
QuoteLink :: a <~ AtomT => Atom a -> Atom a 
BindLink :: (v <~ VariableT, p <~ AtomT, q <~ AtomT) => Atom v -> Atom p -> Atom q -> Atom BindT 

Instances

data Gen a where Source

Gen groups all the atoms that are children of the atom type a.

Constructors

Gen :: (Typeable a, b <~ a) => Atom b -> Gen a 

Instances

Typeable AtomType a => Eq (Gen a) 
Show (Gen a) 

appGen :: (forall b. (Typeable a, b <~ a) => Atom b -> c) -> Gen a -> c Source

appGen evaluates a given function with the atom type instance wrapped inside the Gen type.

type AtomGen = Gen AtomT Source

AtomGen is a general atom type hiding the type variables. (necessary when working with many instances of different atoms, for example, for lists of general atoms)

AtomSpace Syntactic Sugar

noTv :: Maybe TruthVal Source

TruthVal syntactic sugar.

atomList :: Typeable c => [Gen c] -> [Gen c] Source

atomList is simple sugar notation for listing atoms, using operators |> and \>. For example, if you want to define a list of atoms:

l :: [AtomGen]
l = atomList
      |> ConceptNode "concept1" noTv
      |> PredicateNode "predicate2" noTv
      \> ConceptNode "lastconcept" noTv

(|>) :: (Typeable c, b <~ c) => ([Gen c] -> a) -> Atom b -> [Gen c] -> a infixl 5 Source

|> and \> operators are provided for easier notation of list of Gen elements when working with atoms of random arity (e.g. ListLink).

  • Without sugar:
    list :: Atom ListT
    list = ListLink [ Gen (ConceptNode "someConcept1" noTv)
                    , Gen (PredicateNode "somePredicate1" noTv)
                    , Gen (PredicateNode "somePredicate2" noTv)
                    , Gen (ListLink [ Gen (ConceptNode "someConcept2" noTv)
                                    , Gen (PredicateNode "somePredicate3" noTv)
                                    ]
                          )
                    ]
    
  • With sugar:
    list :: Atom ListT
    list = ListLink |> ConceptNode "someConcept1" noTv
                    |> PredicateNode "somePredicate1" noTv
                    |> PredicateNode "somePredicate2" noTv
                    \> ListLink |> ConceptNode "someConcept2" noTv
                                \> PredicateNode "somePredicate3" noTv
    

(\>) :: (Typeable c, b <~ c) => ([Gen c] -> a) -> Atom b -> a infixr 4 Source

AtomSpace Phantom Types

data AtomType Source

AtomType is automatically generated by Template Haskell (based on: atom_types.script file)

Instances

Eq AtomType 
Read AtomType 
Show AtomType 
Typeable * AtomType 
Typeable AtomType VirtualT 
Typeable AtomType VariableT 
Typeable AtomType VariableListT 
Typeable AtomType UnorderedT 
Typeable AtomType TypedVariableT 
Typeable AtomType TypeT 
Typeable AtomType TypeChoiceT 
Typeable AtomType TimesT 
Typeable AtomType SubsetT 
Typeable AtomType SimilarityT 
Typeable AtomType SetT 
Typeable AtomType SequentialAndT 
Typeable AtomType ScholemT 
Typeable AtomType SchemaT 
Typeable AtomType SchemaExecutionT 
Typeable AtomType SchemaEvaluationT 
Typeable AtomType SatisfyingSetT 
Typeable AtomType SatisfactionT 
Typeable AtomType RemoveT 
Typeable AtomType QuoteT 
Typeable AtomType QuantityT 
Typeable AtomType PutT 
Typeable AtomType ProcedureT 
Typeable AtomType PredicateT 
Typeable AtomType PlusT 
Typeable AtomType PatternT 
Typeable AtomType OrderedT 
Typeable AtomType OrT 
Typeable AtomType NumberT 
Typeable AtomType NotypeT 
Typeable AtomType NotT 
Typeable AtomType NodeT 
Typeable AtomType MemberT 
Typeable AtomType ListT 
Typeable AtomType LinkT 
Typeable AtomType LambdaT 
Typeable AtomType IntensionalSimilarityT 
Typeable AtomType IntensionalInheritanceT 
Typeable AtomType InsertT 
Typeable AtomType InheritanceT 
Typeable AtomType ImplicationT 
Typeable AtomType GroundedSchemaT 
Typeable AtomType GroundedProcedureT 
Typeable AtomType GroundedPredicateT 
Typeable AtomType GreaterThanT 
Typeable AtomType GetT 
Typeable AtomType FunctionT 
Typeable AtomType FreeT 
Typeable AtomType ForAllT 
Typeable AtomType FoldT 
Typeable AtomType ExtensionalSimilarityT 
Typeable AtomType ExistsT 
Typeable AtomType ExecutionOutputT 
Typeable AtomType ExecutionT 
Typeable AtomType EvaluationT 
Typeable AtomType EquivalenceT 
Typeable AtomType EqualT 
Typeable AtomType DeleteT 
Typeable AtomType DefinedRelationshipT 
Typeable AtomType DefineT 
Typeable AtomType ContextT 
Typeable AtomType ConceptT 
Typeable AtomType ChoiceT 
Typeable AtomType BindT 
Typeable AtomType AverageT 
Typeable AtomType AttractionT 
Typeable AtomType AtomT 
Typeable AtomType AssociativeT 
Typeable AtomType AssignT 
Typeable AtomType ArithmeticT 
Typeable AtomType AndT 
Typeable AtomType AnchorT 
Typeable AtomType AbsentT 
Typeable (AtomType -> *) Atom 

type (<~) a b = (Typeable a, ParConst a (Up b)) infix 9 Source

<~ builds a list of constraints to assert that all the ancestors of b (included b itself) are ancestors of a.