Safe Haskell | None |
---|---|
Language | Haskell98 |
OpenCog.AtomSpace
Contents
Description
This library defines Haskell Bindings for the AtomSpace.
- data AtomSpace a
- data AtomSpaceObj
- getParent :: AtomSpaceObj -> Maybe AtomSpaceObj
- newAtomSpace :: Maybe AtomSpaceObj -> IO AtomSpaceObj
- onAtomSpace :: AtomSpaceObj -> AtomSpace a -> IO a
- (<:) :: AtomSpaceObj -> AtomSpace a -> IO a
- runOnNewAtomSpace :: AtomSpace a -> IO a
- insert :: Typeable a => Atom a -> AtomSpace ()
- remove :: Typeable a => Atom a -> AtomSpace Bool
- get :: a <~ AtomT => Atom a -> AtomSpace (Maybe (Atom a))
- debug :: AtomSpace ()
- cogBind :: Atom BindT -> AtomSpace (Maybe AtomGen)
- printAtom :: Typeable a => Atom a -> IO ()
- showAtom :: Typeable a => Atom a -> String
- data TruthVal
- type AtomName = String
- data Atom a where
- 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
- data Gen a where
- appGen :: (forall b. (Typeable a, b <~ a) => Atom b -> c) -> Gen a -> c
- type AtomGen = Gen AtomT
- stv :: Double -> Double -> Maybe TruthVal
- ctv :: Double -> Double -> Double -> Maybe TruthVal
- itv :: Double -> Double -> Double -> Double -> Double -> Maybe TruthVal
- ftv :: Double -> Double -> Maybe TruthVal
- ptv :: Double -> Double -> Double -> Maybe TruthVal
- noTv :: Maybe TruthVal
- atomList :: Typeable c => [Gen c] -> [Gen c]
- (|>) :: (Typeable c, b <~ c) => ([Gen c] -> a) -> Atom b -> [Gen c] -> a
- (\>) :: (Typeable c, b <~ c) => ([Gen c] -> a) -> Atom b -> a
- data AtomType
- = AbsentT
- | AnchorT
- | AndT
- | ArithmeticT
- | AssignT
- | AssociativeT
- | AtomT
- | AttractionT
- | AverageT
- | BindT
- | ChoiceT
- | ConceptT
- | ContextT
- | DefineT
- | DefinedRelationshipT
- | DeleteT
- | EqualT
- | EquivalenceT
- | EvaluationT
- | ExecutionT
- | ExecutionOutputT
- | ExistsT
- | ExtensionalSimilarityT
- | FoldT
- | ForAllT
- | FreeT
- | FunctionT
- | GetT
- | GreaterThanT
- | GroundedPredicateT
- | GroundedProcedureT
- | GroundedSchemaT
- | ImplicationT
- | InheritanceT
- | InsertT
- | IntensionalInheritanceT
- | IntensionalSimilarityT
- | LambdaT
- | LinkT
- | ListT
- | MemberT
- | NodeT
- | NotT
- | NotypeT
- | NumberT
- | OrT
- | OrderedT
- | PatternT
- | PlusT
- | PredicateT
- | ProcedureT
- | PutT
- | QuantityT
- | QuoteT
- | RemoveT
- | SatisfactionT
- | SatisfyingSetT
- | SchemaEvaluationT
- | SchemaExecutionT
- | SchemaT
- | ScholemT
- | SequentialAndT
- | SetT
- | SimilarityT
- | SubsetT
- | TimesT
- | TypeChoiceT
- | TypeT
- | TypedVariableT
- | UnorderedT
- | VariableListT
- | VariableT
- | VirtualT
- type (<~) a b = (Typeable a, ParConst a (Up b))
AtomSpace Environment
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.
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
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
showAtom :: Typeable a => Atom a -> String Source
showAtom
shows an atom in opencog notation (indented notation).
AtomSpace Main Data Types
TruthVal
represent the different types of TruthValues.
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
- If it is of a fixed arity:
Also, you have to modify the module Internal. Adding proper case clauses for this new atom type to the functions "toRaw" and "fromRaw".
Constructors
Gen
groups all the atoms that are children of the atom type a.
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
(|>) :: (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
AtomSpace Phantom Types
AtomType
is automatically generated by Template Haskell
(based on: atom_types.script file)
Constructors
Instances