ideas-1.8: Feedback services for intelligent tutoring systems

Maintainerbastiaan.heeren@ou.nl
Stabilityprovisional
Portabilityportable (depends on ghc)
Safe HaskellNone
LanguageHaskell98

Ideas.Common.Id

Contents

Description

Many entities of the Ideas framework carry an Id for identification. Identifiers have a hierarchical structure of an arbitrary depth (e.g. algebra.equation or a.b.c). Valid symbols for identifiers are the alpha-numerical characters, together with - and _. Each identifier carries a description and a hash value for fast comparison.

Functionality for identifiers is provided by means of three type classes:

  • Type class IsId for constructing identifiers
  • Type class HasId for accessing (and changing) the identifier of an entity. Instances of this type class must always have exactly one identifier (although this identifier can be empty).
  • Type class Identify for labeling entities with an identifier. Instances of this type class typically allow labels to appear at multiple locations within their structure.

The Id datatype implements the Monoid interface.

Synopsis

Constructing identifiers

data Id Source #

Abstract data type for identifiers with a hierarchical name, carrying a description. The data type provides a fast comparison implementation.

Instances
Eq Id Source # 
Instance details

Defined in Ideas.Common.Id

Methods

(==) :: Id -> Id -> Bool #

(/=) :: Id -> Id -> Bool #

Ord Id Source # 
Instance details

Defined in Ideas.Common.Id

Methods

compare :: Id -> Id -> Ordering #

(<) :: Id -> Id -> Bool #

(<=) :: Id -> Id -> Bool #

(>) :: Id -> Id -> Bool #

(>=) :: Id -> Id -> Bool #

max :: Id -> Id -> Id #

min :: Id -> Id -> Id #

Read Id Source # 
Instance details

Defined in Ideas.Common.Id

Show Id Source # 
Instance details

Defined in Ideas.Common.Id

Methods

showsPrec :: Int -> Id -> ShowS #

show :: Id -> String #

showList :: [Id] -> ShowS #

Semigroup Id Source # 
Instance details

Defined in Ideas.Common.Id

Methods

(<>) :: Id -> Id -> Id #

sconcat :: NonEmpty Id -> Id #

stimes :: Integral b => b -> Id -> Id #

Monoid Id Source # 
Instance details

Defined in Ideas.Common.Id

Methods

mempty :: Id #

mappend :: Id -> Id -> Id #

mconcat :: [Id] -> Id #

Arbitrary Id Source # 
Instance details

Defined in Ideas.Common.Id

Methods

arbitrary :: Gen Id

shrink :: Id -> [Id]

ToHTML Id Source # 
Instance details

Defined in Ideas.Common.Id

HasId Id Source # 
Instance details

Defined in Ideas.Common.Id

Methods

getId :: Id -> Id Source #

changeId :: (Id -> Id) -> Id -> Id Source #

IsId Id Source # 
Instance details

Defined in Ideas.Common.Id

Methods

newId :: Id -> Id Source #

concatId :: [Id] -> Id Source #

class IsId a where Source #

Type class IsId for constructing identifiers. Examples are newId "algebra.equation", newId ("a", "b", "c"), and newId () for the empty identifier.

Minimal complete definition

newId

Methods

newId :: a -> Id Source #

concatId :: [a] -> Id Source #

Instances
IsId Char Source # 
Instance details

Defined in Ideas.Common.Id

Methods

newId :: Char -> Id Source #

concatId :: [Char] -> Id Source #

IsId () Source # 
Instance details

Defined in Ideas.Common.Id

Methods

newId :: () -> Id Source #

concatId :: [()] -> Id Source #

IsId Id Source # 
Instance details

Defined in Ideas.Common.Id

Methods

newId :: Id -> Id Source #

concatId :: [Id] -> Id Source #

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

Defined in Ideas.Common.Id

Methods

newId :: [a] -> Id Source #

concatId :: [[a]] -> Id Source #

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

Defined in Ideas.Common.Id

Methods

newId :: Maybe a -> Id Source #

concatId :: [Maybe a] -> Id Source #

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

Defined in Ideas.Common.Id

Methods

newId :: Either a b -> Id Source #

concatId :: [Either a b] -> Id Source #

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

Defined in Ideas.Common.Id

Methods

newId :: (a, b) -> Id Source #

concatId :: [(a, b)] -> Id Source #

(IsId a, IsId b, IsId c) => IsId (a, b, c) Source # 
Instance details

Defined in Ideas.Common.Id

Methods

newId :: (a, b, c) -> Id Source #

concatId :: [(a, b, c)] -> Id Source #

(#) :: (IsId a, IsId b) => a -> b -> Id infixr 8 Source #

Appends two identifiers. Both parameters are overloaded.

Accessing (and changing) identifiers

class HasId a where Source #

Type classfor accessing (and changing) the identifier of an entity.

Minimal complete definition

getId, changeId

Methods

getId :: a -> Id Source #

changeId :: (Id -> Id) -> a -> a Source #

Instances
HasId Id Source # 
Instance details

Defined in Ideas.Common.Id

Methods

getId :: Id -> Id Source #

changeId :: (Id -> Id) -> Id -> Id Source #

HasId ViewPackage Source # 
Instance details

Defined in Ideas.Common.View

HasId Symbol Source # 
Instance details

Defined in Ideas.Common.Rewriting.Term

Methods

getId :: Symbol -> Id Source #

changeId :: (Id -> Id) -> Symbol -> Symbol Source #

HasId Binding Source # 
Instance details

Defined in Ideas.Common.Environment

Methods

getId :: Binding -> Id Source #

changeId :: (Id -> Id) -> Binding -> Binding Source #

HasId Service Source # 
Instance details

Defined in Ideas.Service.Types

Methods

getId :: Service -> Id Source #

changeId :: (Id -> Id) -> Service -> Service Source #

HasId DomainReasoner Source # 
Instance details

Defined in Ideas.Service.DomainReasoner

HasId (Predicate a) Source # 
Instance details

Defined in Ideas.Common.Predicate

Methods

getId :: Predicate a -> Id Source #

changeId :: (Id -> Id) -> Predicate a -> Predicate a Source #

HasId (Constraint a) Source # 
Instance details

Defined in Ideas.Common.Constraint

Methods

getId :: Constraint a -> Id Source #

changeId :: (Id -> Id) -> Constraint a -> Constraint a Source #

HasId (Ref a) Source # 
Instance details

Defined in Ideas.Common.Environment

Methods

getId :: Ref a -> Id Source #

changeId :: (Id -> Id) -> Ref a -> Ref a Source #

HasId (RewriteRule a) Source # 
Instance details

Defined in Ideas.Common.Rewriting.RewriteRule

HasId (Rule a) Source # 
Instance details

Defined in Ideas.Common.Rule.Abstract

Methods

getId :: Rule a -> Id Source #

changeId :: (Id -> Id) -> Rule a -> Rule a Source #

HasId (Decl f) Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

getId :: Decl f -> Id Source #

changeId :: (Id -> Id) -> Decl f -> Decl f Source #

HasId (Dynamic a) Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

getId :: Dynamic a -> Id Source #

changeId :: (Id -> Id) -> Dynamic a -> Dynamic a Source #

HasId (Leaf a) Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

getId :: Leaf a -> Id Source #

changeId :: (Id -> Id) -> Leaf a -> Leaf a Source #

HasId (LabeledStrategy a) Source # 
Instance details

Defined in Ideas.Common.Strategy.Abstract

HasId (Exercise a) Source # 
Instance details

Defined in Ideas.Common.Exercise

Methods

getId :: Exercise a -> Id Source #

changeId :: (Id -> Id) -> Exercise a -> Exercise a Source #

HasId (State a) Source # 
Instance details

Defined in Ideas.Service.State

Methods

getId :: State a -> Id Source #

changeId :: (Id -> Id) -> State a -> State a Source #

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

Defined in Ideas.Common.Id

Methods

getId :: Either a b -> Id Source #

changeId :: (Id -> Id) -> Either a b -> Either a b Source #

HasId (Isomorphism a b) Source # 
Instance details

Defined in Ideas.Common.View

Methods

getId :: Isomorphism a b -> Id Source #

changeId :: (Id -> Id) -> Isomorphism a b -> Isomorphism a b Source #

HasId (View a b) Source # 
Instance details

Defined in Ideas.Common.View

Methods

getId :: View a b -> Id Source #

changeId :: (Id -> Id) -> View a b -> View a b Source #

unqualified :: HasId a => a -> String Source #

Get the unqualified part of the identifier (i.e., last string).

qualifiers :: HasId a => a -> [String] Source #

Get the list of qualifiers of the identifier (i.e., everything but the last string).

qualification :: HasId a => a -> String Source #

Get the qualified part of the identifier. If the identifier consists of more than one part, the parts are separated by a period (.).

describe :: HasId a => String -> a -> a Source #

Give a description for the current entity. If there already is a description, both strings are combined.

description :: HasId a => a -> String Source #

Get the current description.

showId :: HasId a => a -> String Source #

Show the identifier.

compareId :: HasId a => a -> a -> Ordering Source #

Compare two identifiers based on their names. Use compare for a fast ordering based on hash values.

Labeling with identifiers

class HasId a => Identify a where Source #

Type class for labeling entities with an identifier

Minimal complete definition

(@>)

Methods

(@>) :: IsId n => n -> a -> a Source #

Instances
Identify (Predicate a) Source # 
Instance details

Defined in Ideas.Common.Predicate

Methods

(@>) :: IsId n => n -> Predicate a -> Predicate a Source #

Identify (Isomorphism a b) Source # 
Instance details

Defined in Ideas.Common.View

Methods

(@>) :: IsId n => n -> Isomorphism a b -> Isomorphism a b Source #

Identify (View a b) Source # 
Instance details

Defined in Ideas.Common.View

Methods

(@>) :: IsId n => n -> View a b -> View a b Source #