hasklepias-0.8.3: Define features from events
Copyright(c) NoviSci Inc 2020
LicenseBSD3
Maintainerbsaul@novisci.com
Safe HaskellNone
LanguageHaskell2010

EventData

Description

 
Synopsis

Documentation

type Event a = PairedInterval Context a Source #

An Event a is simply a pair (Interval a, Context).

type Events a = [Event a] Source #

A List of Event a

NOTE (20190911): I (B. Saul) am starting out the Events type as a list of the Event type. This may be not be the optimal approach, especially with regards to lookup/filtering the list. Ideally, we could do one pass through the ordered container (whatever it is) to identify events by concept; rather than repeated evaluations of the lookup predicates. This could be handled by, for example, representing Events has a Map with a list of concept indices. But this gets us off the ground.

type ConceptEvent a = PairedInterval Concepts a Source #

An event containing only concepts and an interval

event :: Interval a -> Context -> Event a Source #

A smart constructor for 'Event a's.

ctxt :: Event a -> Context Source #

Access the Context of an 'Event a'.

toConceptEvent :: (Show a, Ord a) => Event a -> ConceptEvent a Source #

Drops an Event to a ConceptEvent by moving the concepts in the data position in the paired interval and throwing out the facts and source.

class HasConcept a where Source #

The HasConcept typeclass provides predicate functions for determining whether an a has a concept.

Minimal complete definition

hasConcept

Methods

hasConcept :: a -> Text -> Bool Source #

Does an a have a particular Concept?

hasConcepts :: a -> [Text] -> Bool Source #

Does an a have *any* of a list of Concepts?

hasAllConcepts :: a -> [Text] -> Bool Source #

Does an a have *all* of a list of Concepts?

Instances

Instances details
HasConcept Concepts Source # 
Instance details

Defined in EventData.Context

HasConcept Context Source # 
Instance details

Defined in EventData.Context

HasConcept (ConceptEvent a) Source # 
Instance details

Defined in EventData

HasConcept (Event a) Source # 
Instance details

Defined in EventData

data Concepts Source #

Concepts is a Set of Conceptss.

Instances

Instances details
Eq Concepts Source # 
Instance details

Defined in EventData.Context

Show Concepts Source # 
Instance details

Defined in EventData.Context

Semigroup Concepts Source # 
Instance details

Defined in EventData.Context

Monoid Concepts Source # 
Instance details

Defined in EventData.Context

FromJSON Concepts Source # 
Instance details

Defined in EventData.Aeson

HasConcept Concepts Source # 
Instance details

Defined in EventData.Context

(Ord a, Show a, Arbitrary (Interval a)) => Arbitrary (ConceptEvent a) Source # 
Instance details

Defined in EventData.Arbitrary

HasConcept (ConceptEvent a) Source # 
Instance details

Defined in EventData

data Concept Source #

A Concept is textual "tag" for a context.

Instances

Instances details
Eq Concept Source # 
Instance details

Defined in EventData.Context

Methods

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

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

Ord Concept Source # 
Instance details

Defined in EventData.Context

Show Concept Source # 
Instance details

Defined in EventData.Context

Arbitrary Concept Source # 
Instance details

Defined in EventData.Context.Arbitrary

FromJSON Concept Source # 
Instance details

Defined in EventData.Aeson

data Context Source #

A Context consists of three parts: concepts, facts, and source.

At this time, facts and source are simply stubs to be fleshed out in later versions of hasklepias.

Constructors

Context 

Fields

Instances

Instances details
Eq Context Source # 
Instance details

Defined in EventData.Context

Methods

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

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

Show Context Source # 
Instance details

Defined in EventData.Context

Semigroup Context Source # 
Instance details

Defined in EventData.Context

Monoid Context Source # 
Instance details

Defined in EventData.Context

Arbitrary Context Source # 
Instance details

Defined in EventData.Context.Arbitrary

FromJSON Context Source # 
Instance details

Defined in EventData.Aeson

HasConcept Context Source # 
Instance details

Defined in EventData.Context

Arbitrary (Interval a) => Arbitrary (Event a) Source # 
Instance details

Defined in EventData.Arbitrary

Methods

arbitrary :: Gen (Event a) #

shrink :: Event a -> [Event a] #

(FromJSON a, Show a, IntervalSizeable a b) => FromJSON (Event a) Source # 
Instance details

Defined in EventData.Aeson

HasConcept (Event a) Source # 
Instance details

Defined in EventData

packConcept :: Text -> Concept Source #

Pack text into a concept

Orphan instances