| Copyright | (c) NoviSci Inc 2020 |
|---|---|
| License | BSD3 |
| Maintainer | bsaul@novisci.com |
| Safe Haskell | None |
| Language | Haskell2010 |
Hasklepias
Description
See the examples folder and manual for further documentation.
Synopsis
- type Event a = PairedInterval Context a
- type Events a = [Event a]
- type ConceptEvent a = PairedInterval Concepts a
- event :: Interval a -> Context -> Event a
- ctxt :: Event a -> Context
- toConceptEvent :: (Show a, Ord a) => Event a -> ConceptEvent a
- toConceptEventOf :: (Show a, Ord a) => [Concept] -> Event a -> ConceptEvent a
- mkConceptEvent :: (Show a, Ord a) => Interval a -> Concepts -> ConceptEvent a
- data Context = Context {}
- concepts :: Lens' Context Concepts
- facts :: Lens' Context Domain
- source :: Lens' Context (Maybe Source)
- context :: Domain -> Concepts -> Context
- data Concept
- data Concepts
- toConcepts :: Set Concept -> Concepts
- getConcepts :: Concepts -> Set Concept
- packConcept :: Text -> Concept
- unpackConcept :: Concept -> Text
- packConcepts :: [Text] -> Concepts
- unpackConcepts :: Concepts -> [Text]
- class HasConcept a where
- hasConcept :: a -> Text -> Bool
- hasConcepts :: a -> [Text] -> Bool
- hasAllConcepts :: a -> [Text] -> Bool
- data Source
- data Domain
- _Demographics :: Prism' Domain DemographicsFacts
- newtype DemographicsFacts = DemographicsFacts {}
- data DemographicsInfo = DemographicsInfo {}
- data DemographicsField
- demo :: Iso' DemographicsFacts DemographicsInfo
- field :: Lens' DemographicsInfo DemographicsField
- info :: Lens' DemographicsInfo (Maybe Text)
- _Enrollment :: Prism' Domain EnrollmentFacts
- newtype EnrollmentFacts = EnrollmentFacts {
- _plan :: ()
- isEnrollmentEvent :: Predicate (Event a)
- isStateFactEvent :: Predicate (Event a)
- isGenderFactEvent :: Predicate (Event a)
- isBirthYearEvent :: Predicate (Event a)
- containsConcepts :: [Text] -> Predicate (Event a)
- class Predicatable a where
- viewBirthYears :: Witherable f => f (Event a) -> [Year]
- viewGenders :: Witherable f => f (Event a) -> [Text]
- viewStates :: Witherable f => f (Event a) -> [Text]
- previewDemoInfo :: Domain -> Maybe Text
- previewBirthYear :: Domain -> Maybe Year
- parseEventIntLines :: (FromJSON a, Show a, IntervalSizeable a b) => ByteString -> ([String], [Event a])
- parseEventDayLines :: (FromJSON a, Show a, IntervalSizeable a b) => ByteString -> ([String], [Event a])
- generateEventsInt :: Int -> IO [Event Int]
- data FeatureData d
- data MissingReason
- data KnownSymbol name => Feature name d
- data FeatureN d
- featureDataL :: MissingReason -> FeatureData d
- featureDataR :: d -> FeatureData d
- missingBecause :: MissingReason -> FeatureData d
- makeFeature :: KnownSymbol name => FeatureData d -> Feature name d
- getFeatureData :: FeatureData d -> Either MissingReason d
- getFData :: Feature name d -> FeatureData d
- getData :: Feature n d -> Either MissingReason d
- getDataN :: FeatureN d -> FeatureData d
- getNameN :: FeatureN d -> Text
- nameFeature :: forall name d. KnownSymbol name => Feature name d -> FeatureN d
- data Definition d where
- D1 :: (b -> a) -> Definition (f1 b -> f0 a)
- D1A :: (b -> f0 a) -> Definition (f1 b -> f0 a)
- D2 :: (c -> b -> a) -> Definition (f2 c -> f1 b -> f0 a)
- D2A :: (c -> b -> f0 a) -> Definition (f2 c -> f1 b -> f0 a)
- D3 :: (d -> c -> b -> a) -> Definition (f3 d -> f2 c -> f1 b -> f0 a)
- D3A :: (d -> c -> b -> f0 a) -> Definition (f3 d -> f2 c -> f1 b -> f0 a)
- D4 :: (e -> d -> c -> b -> a) -> Definition (f4 e -> f3 d -> f2 c -> f1 b -> f0 a)
- D4A :: (e -> d -> c -> b -> f0 a) -> Definition (f4 e -> f3 d -> f2 c -> f1 b -> f0 a)
- class Define inputs def | def -> inputs where
- define :: inputs -> Definition def
- class DefineA inputs def | def -> inputs where
- defineA :: inputs -> Definition def
- class Eval def args return | def -> args return where
- eval :: Definition def -> args -> return
- data Attributes = MkAttributes {}
- data Role
- data Purpose = MkPurpose {}
- class KnownSymbol name => HasAttributes name d where
- getAttributes :: f name d -> Attributes
- emptyAttributes :: Attributes
- basicAttributes :: Text -> Text -> [Role] -> [Text] -> Attributes
- emptyPurpose :: Purpose
- data Featureable = forall d.(Show d, ToJSON d, ShapeOutput d) => MkFeatureable d Attributes
- packFeature :: (KnownSymbol n, Show d, ToJSON d, Typeable d, HasAttributes n d) => Feature n d -> Featureable
- getFeatureableAttrs :: Featureable -> Attributes
- data Featureset
- newtype FeaturesetList = MkFeaturesetList (NonEmpty Featureset)
- featureset :: NonEmpty Featureable -> Featureset
- getFeatureset :: Featureset -> NonEmpty Featureable
- getFeaturesetAttrs :: Featureset -> NonEmpty Attributes
- getFeaturesetList :: FeaturesetList -> NonEmpty Featureset
- tpose :: FeaturesetList -> FeaturesetList
- class ToJSON a => ShapeOutput a where
- dataOnly :: a -> OutputShape b
- nameOnly :: a -> OutputShape b
- attrOnly :: a -> OutputShape b
- nameData :: a -> OutputShape b
- nameAttr :: a -> OutputShape b
- data OutputShape d
- buildIsEnrolled :: (Intervallic i0 a, Monoid (container (Interval a)), Applicative container, Witherable container) => Predicate (Event a) -> Definition (Feature indexName (Index i0 a) -> Feature eventsName (container (Event a)) -> Feature varName Status)
- buildContinuousEnrollment :: (Monoid (container (Interval a)), Monoid (container (Maybe (Interval a))), Applicative container, Witherable container, IntervalSizeable a b) => (Index i0 a -> AssessmentInterval a) -> Predicate (Event a) -> b -> Definition (Feature indexName (Index i0 a) -> Feature eventsName (container (Event a)) -> Feature prevName Status -> Feature varName Status)
- buildNofX :: (Intervallic i a, Witherable container) => (Bool -> outputType) -> Natural -> (Index i a -> AssessmentInterval a) -> ComparativePredicateOf2 (AssessmentInterval a) (Event a) -> Predicate (Event a) -> Definition (Feature indexName (Index i a) -> Feature eventsName (container (Event a)) -> Feature varName outputType)
- buildNofXBool :: (Intervallic i a, Witherable container) => Natural -> (Index i a -> AssessmentInterval a) -> ComparativePredicateOf2 (AssessmentInterval a) (Event a) -> Predicate (Event a) -> Definition (Feature indexName (Index i a) -> Feature eventsName (container (Event a)) -> Feature varName Bool)
- buildNofXBinary :: (Intervallic i a, Witherable container) => Natural -> (Index i a -> AssessmentInterval a) -> ComparativePredicateOf2 (AssessmentInterval a) (Event a) -> Predicate (Event a) -> Definition (Feature indexName (Index i a) -> Feature eventsName (container (Event a)) -> Feature varName Binary)
- buildNofXBinaryConcurBaseline :: (Intervallic i0 a, Witherable t, IntervalSizeable a b, Baseline i0 a) => Natural -> b -> Predicate (Event a) -> Definition (Feature indexName (Index i0 a) -> Feature eventsName (t (Event a)) -> Feature varName Binary)
- buildNofConceptsBinaryConcurBaseline :: (Intervallic i0 a, Witherable t, IntervalSizeable a b, Baseline i0 a) => Natural -> b -> [Text] -> Definition (Feature indexName (Index i0 a) -> Feature eventsName (t (Event a)) -> Feature varName Bool)
- buildNofXWithGap :: (Intervallic i a, IntervalSizeable a b, IntervalCombinable i a, Witherable container) => (Bool -> outputType) -> Natural -> b -> (Index i a -> AssessmentInterval a) -> ComparativePredicateOf2 (AssessmentInterval a) (Event a) -> Predicate (Event a) -> Definition (Feature indexName (Index i a) -> Feature eventsName (container (Event a)) -> Feature varName outputType)
- buildNofXWithGapBool :: (Intervallic i a, IntervalSizeable a b, IntervalCombinable i a, Witherable container) => Natural -> b -> (Index i a -> AssessmentInterval a) -> ComparativePredicateOf2 (AssessmentInterval a) (Event a) -> Predicate (Event a) -> Definition (Feature indexName (Index i a) -> Feature eventsName (container (Event a)) -> Feature varName Bool)
- buildNofXWithGapBinary :: (Intervallic i a, IntervalSizeable a b, IntervalCombinable i a, Witherable container) => Natural -> b -> (Index i a -> AssessmentInterval a) -> ComparativePredicateOf2 (AssessmentInterval a) (Event a) -> Predicate (Event a) -> Definition (Feature indexName (Index i a) -> Feature eventsName (container (Event a)) -> Feature varName Binary)
- buildNofUniqueBegins :: (Intervallic i a, IntervalSizeable a b, Witherable container) => (Index i a -> AssessmentInterval a) -> ComparativePredicateOf2 (AssessmentInterval a) (Event a) -> Predicate (Event a) -> Definition (Feature indexName (Index i a) -> Feature eventsName (container (Event a)) -> Feature varName [(EventTime b, Count)])
- isNotEmpty :: [a] -> Bool
- atleastNofX :: Int -> [Text] -> Events a -> Bool
- anyGapsWithinAtLeastDuration :: (IntervalSizeable a b, Intervallic i0 a, IntervalCombinable i1 a, Monoid (t (Interval a)), Monoid (t (Maybe (Interval a))), Applicative t, Witherable t) => b -> i0 a -> t (i1 a) -> Bool
- allGapsWithinLessThanDuration :: (IntervalSizeable a b, Intervallic i0 a, IntervalCombinable i1 a, Monoid (t (Interval a)), Monoid (t (Maybe (Interval a))), Applicative t, Witherable t) => b -> i0 a -> t (i1 a) -> Bool
- nthConceptOccurrence :: Filterable f => (f (Event a) -> Maybe (Event a)) -> [Text] -> f (Event a) -> Maybe (Event a)
- firstConceptOccurrence :: Witherable f => [Text] -> f (Event a) -> Maybe (Event a)
- allPairs :: Applicative f => f a -> f b -> f (a, b)
- pairs :: [a] -> [(a, a)]
- splitByConcepts :: Filterable f => [Text] -> [Text] -> f (Event a) -> (f (Event a), f (Event a))
- makeConceptsFilter :: Filterable f => [Text] -> f (Event a) -> f (Event a)
- makePairedFilter :: Ord a => ComparativePredicateOf2 (i0 a) (PairedInterval b a) -> i0 a -> (b -> Bool) -> [PairedInterval b a] -> [PairedInterval b a]
- yearFromDay :: Day -> Year
- monthFromDay :: Day -> MonthOfYear
- dayOfMonthFromDay :: Day -> DayOfMonth
- lookback :: (Intervallic i a, IntervalSizeable a b) => b -> i a -> Interval a
- lookahead :: (Intervallic i a, IntervalSizeable a b) => b -> i a -> Interval a
- computeAgeAt :: Day -> Day -> Integer
- pairGaps :: (Intervallic i a, IntervalSizeable a b, IntervalCombinable i a) => [i a] -> [Maybe b]
- type F n a = Feature n a
- type Def d = Definition d
- newtype Occurrence what when = MkOccurrence (what, EventTime when)
- makeOccurrence :: OccurrenceReason what => what -> EventTime b -> Occurrence what b
- getOccurrenceReason :: Occurrence what b -> what
- getOccurrenceTime :: Occurrence what b -> EventTime b
- data CensoringReason cr or
- = AdminCensor
- | C cr
- | O or
- class (Ord a, Show a) => OccurrenceReason a
- data CensoredOccurrence censors outcomes b = MkCensoredOccurrence {
- reason :: CensoringReason censors outcomes
- time :: MaybeCensored (EventTime b)
- adminCensor :: EventTime b -> CensoredOccurrence c o b
- newtype Subject d = MkSubject (ID, d)
- type ID = Text
- newtype Population d = MkPopulation [Subject d]
- data ObsUnit d = MkObsUnit {}
- newtype CohortData d = MkCohortData {
- getObsData :: [ObsUnit d]
- newtype Cohort d = MkCohort (Maybe AttritionInfo, CohortData d)
- data CohortSpec d1 d0
- newtype AttritionInfo = MkAttritionInfo (NonEmpty (CohortStatus, Natural))
- specifyCohort :: (d1 -> Criteria) -> (d1 -> d0) -> CohortSpec d1 d0
- makeObsUnitFeatures :: (d1 -> d0) -> Subject d1 -> ObsUnit d0
- evalCohort :: CohortSpec d1 d0 -> Population d1 -> Cohort d0
- getCohortIDs :: Cohort d -> [ID]
- getCohortData :: Cohort d -> [d]
- getAttritionInfo :: Cohort d -> Maybe AttritionInfo
- data Index i a
- makeIndex :: Intervallic i a => i a -> Index i a
- data BaselineInterval a
- class Intervallic i a => Baseline i a where
- baseline :: IntervalSizeable a b => b -> Index i a -> BaselineInterval a
- baselineBefore :: IntervalSizeable a b => b -> b -> Index i a -> BaselineInterval a
- data FollowupInterval a
- class Intervallic i a => Followup i a where
- followup :: (IntervalSizeable a b, Intervallic i a) => b -> Index i a -> FollowupInterval a
- followupMetBy :: (IntervalSizeable a b, Intervallic i a) => b -> Index i a -> FollowupInterval a
- followupAfter :: (IntervalSizeable a b, Intervallic i a) => b -> b -> Index i a -> FollowupInterval a
- data AssessmentInterval a
- makeBaselineFromIndex :: (Baseline i a, IntervalSizeable a b) => b -> Index i a -> AssessmentInterval a
- makeBaselineBeforeIndex :: (Baseline i a, IntervalSizeable a b) => b -> b -> Index i a -> AssessmentInterval a
- makeFollowupFromIndex :: (Followup i a, IntervalSizeable a b) => b -> Index i a -> AssessmentInterval a
- makeFollowupMeetingIndex :: (Followup i a, IntervalSizeable a b) => b -> Index i a -> AssessmentInterval a
- makeFollowupAfterIndex :: (Followup i a, IntervalSizeable a b) => b -> b -> Index i a -> AssessmentInterval a
- data Criterion
- newtype Criteria = MkCriteria {
- getCriteria :: NonEmpty (Natural, Criterion)
- data Status
- data CohortStatus
- = Included
- | ExcludedBy (Natural, Text)
- criterion :: KnownSymbol n => Feature n Status -> Criterion
- criteria :: NonEmpty Criterion -> Criteria
- excludeIf :: Bool -> Status
- includeIf :: Bool -> Status
- initStatusInfo :: Criteria -> NonEmpty CohortStatus
- checkCohortStatus :: Criteria -> CohortStatus
- parsePopulationLines :: (FromJSON a, Show a, IntervalSizeable a b) => ByteString -> ([ParseError], Population (Events a))
- parsePopulationIntLines :: ByteString -> ([ParseError], Population (Events Int))
- parsePopulationDayLines :: ByteString -> ([ParseError], Population (Events Day))
- newtype ParseError = MkParseError (Natural, Text)
- data CohortShape d
- class ShapeCohort d where
- colWise :: Cohort d -> CohortShape ColumnWise
- rowWise :: Cohort d -> CohortShape RowWise
- toJSONCohortShape :: CohortShape shape -> Value
- makeCohortApp :: (FromJSON a, Show a, IntervalSizeable a b, ToJSON d0, ShapeCohort d0) => String -> String -> (Cohort d0 -> CohortShape shape) -> [CohortSpec (Events a) d0] -> IO ()
- module Stype.Numeric
- module Stype.Categorical
- module Stype.Aeson
- module Hasklepias.Reexports
- module Hasklepias.ReexportsUnsafe
Events
type Event a = PairedInterval Context a Source #
An Event a is simply a pair (Interval a, Context).
type ConceptEvent a = PairedInterval Concepts a Source #
An event containing only concepts and an interval
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.
toConceptEventOf :: (Show a, Ord a) => [Concept] -> Event a -> ConceptEvent a Source #
Creates a new from an ConceptEvent by taking the intersection
of the list of Concepts in the first argument and any Concepts in the Event.
This is a way to keep only the concepts you want in an event.Event
mkConceptEvent :: (Show a, Ord a) => Interval a -> Concepts -> ConceptEvent a Source #
Create a new .ConceptEvent
Event Contexts
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.
Instances
| Eq Context Source # | |
| Show Context Source # | |
| Arbitrary Context Source # | |
| FromJSON Context Source # | |
| HasConcept Context Source # | |
Defined in EventData.Context | |
| Arbitrary (Interval a) => Arbitrary (Event a) Source # | |
| (FromJSON a, Show a, IntervalSizeable a b) => FromJSON (Event a) Source # | |
| HasConcept (Event a) Source # | |
Defined in EventData.Core | |
A Concept is textual "tag" for a context.
Instances
| Eq Concepts Source # | |
| Show Concepts Source # | |
| Semigroup Concepts Source # | |
| Monoid Concepts Source # | |
| FromJSON Concepts Source # | |
| HasConcept Concepts Source # | |
Defined in EventData.Context | |
| (Ord a, Show a, Arbitrary (Interval a)) => Arbitrary (ConceptEvent a) Source # | |
Defined in EventData.Arbitrary | |
| HasConcept (ConceptEvent a) Source # | |
Defined in EventData.Core Methods hasConcept :: ConceptEvent a -> Text -> Bool Source # hasConcepts :: ConceptEvent a -> [Text] -> Bool Source # hasAllConcepts :: ConceptEvent a -> [Text] -> Bool Source # | |
packConcept :: Text -> Concept Source #
Pack text into a concept
unpackConcept :: Concept -> Text Source #
Unpack text from a concept
packConcepts :: [Text] -> Concepts Source #
Put a list of text into a set concepts.
unpackConcepts :: Concepts -> [Text] Source #
Take a set of concepts to a list of text.
class HasConcept a where Source #
The HasConcept typeclass provides predicate functions for determining whether
an a has a concept.
Minimal complete definition
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
| HasConcept Concepts Source # | |
Defined in EventData.Context | |
| HasConcept Context Source # | |
Defined in EventData.Context | |
| HasConcept (ConceptEvent a) Source # | |
Defined in EventData.Core Methods hasConcept :: ConceptEvent a -> Text -> Bool Source # hasConcepts :: ConceptEvent a -> [Text] -> Bool Source # hasAllConcepts :: ConceptEvent a -> [Text] -> Bool Source # | |
| HasConcept (Event a) Source # | |
Defined in EventData.Core | |
Event Domains
Defines the available domains.
Constructors
| Demographics DemographicsFacts | |
| Enrollment EnrollmentFacts | |
| UnimplementedDomain () |
Instances
| Eq Domain Source # | |
| Show Domain Source # | |
| Generic Domain Source # | |
| FromJSON Domain Source # | |
| type Rep Domain Source # | |
Defined in EventData.Context.Domain type Rep Domain = D1 ('MetaData "Domain" "EventData.Context.Domain" "hasklepias-0.17.0-inplace" 'False) (C1 ('MetaCons "Demographics" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DemographicsFacts)) :+: (C1 ('MetaCons "Enrollment" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EnrollmentFacts)) :+: C1 ('MetaCons "UnimplementedDomain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ())))) | |
newtype DemographicsFacts Source #
a demographic fact
Constructors
| DemographicsFacts | |
Fields | |
Instances
data DemographicsInfo Source #
information of a demographic fact
Constructors
| DemographicsInfo | |
Fields
| |
Instances
data DemographicsField Source #
fields available in a demographic fact
Constructors
Instances
newtype EnrollmentFacts Source #
An enrollment fact
Constructors
| EnrollmentFacts | |
Fields
| |
Instances
Predicates
isEnrollmentEvent :: Predicate (Event a) Source #
Predicate for enrollment events
isStateFactEvent :: Predicate (Event a) Source #
Predicate for events containing State facts
isGenderFactEvent :: Predicate (Event a) Source #
Predicate for events containing Gender facts
isBirthYearEvent :: Predicate (Event a) Source #
Predicate for events containing Birth Year facts
class Predicatable a where Source #
Provides methods for composing predicate functions (i.e. a -> Bool) or
Predicates by conjunction or disjunction.
Instances
| Predicatable (Predicate a) Source # | |
| Predicatable (a -> Bool) Source # | |
Accessing data in Events
viewBirthYears :: Witherable f => f (Event a) -> [Year] Source #
Returns a (possibly empty) list of birth years from a set of events
viewGenders :: Witherable f => f (Event a) -> [Text] Source #
Returns a (possibly empty) list of Gender values from a set of events
viewStates :: Witherable f => f (Event a) -> [Text] Source #
Returns a (possibly empty) list of Gender values from a set of events
Parsing Events
parseEventIntLines :: (FromJSON a, Show a, IntervalSizeable a b) => ByteString -> ([String], [Event a]) Source #
Parse Event Int from json lines.
parseEventDayLines :: (FromJSON a, Show a, IntervalSizeable a b) => ByteString -> ([String], [Event a]) Source #
Parse Event Day from json lines.
Generating arbitrary events
Working with Features
Creating Features
Features and FeatureData
data FeatureData d Source #
The FeatureData type is a container for an (almost) arbitrary type d that can
have a "failed" or "missing" state. The failure is represented by the of
an Left, while the data Eitherd is contained in the 's Either.Right
To construct a successful value, use . A missing value can be
constructed with featureDataR or its synonym featureDataL.missingBecause
Instances
data MissingReason Source #
Defines the reasons that a value may be missing. Can be used to
indicate the reason that a FeatureData's data was unable to be derived or does
not need to be derived. Feature
Constructors
| InsufficientData | Insufficient information available to derive data. |
| Other Text | User provided reason for missingness |
Instances
data KnownSymbol name => Feature name d Source #
The is an abstraction for Featurenamed data, where the name is a
*type*. Essentially, it is a container for that assigns a FeatureDataname
to the data.
Except when using to lift data into a pureFeature, Features can only be
derived from other Feature via a .Definition
Instances
| Monad (Feature name) Source # | |
| Functor (Feature name) Source # | |
| Applicative (Feature name) Source # | |
Defined in Features.Compose | |
| Foldable (Feature name) Source # | |
Defined in Features.Compose Methods fold :: Monoid m => Feature name m -> m # foldMap :: Monoid m => (a -> m) -> Feature name a -> m # foldMap' :: Monoid m => (a -> m) -> Feature name a -> m # foldr :: (a -> b -> b) -> b -> Feature name a -> b # foldr' :: (a -> b -> b) -> b -> Feature name a -> b # foldl :: (b -> a -> b) -> b -> Feature name a -> b # foldl' :: (b -> a -> b) -> b -> Feature name a -> b # foldr1 :: (a -> a -> a) -> Feature name a -> a # foldl1 :: (a -> a -> a) -> Feature name a -> a # toList :: Feature name a -> [a] # null :: Feature name a -> Bool # length :: Feature name a -> Int # elem :: Eq a => a -> Feature name a -> Bool # maximum :: Ord a => Feature name a -> a # minimum :: Ord a => Feature name a -> a # | |
| Traversable (Feature name) Source # | |
Defined in Features.Compose | |
| Eq d => Eq (Feature name d) Source # | |
| (KnownSymbol name, Show a) => Show (Feature name a) Source # | |
| (Typeable d, KnownSymbol n, ToJSON d, HasAttributes n d) => ToJSON (Feature n d) Source # | |
Defined in Features.Output | |
| (KnownSymbol n, Show d, ToJSON d, Typeable d, HasAttributes n d) => ShapeOutput (Feature n d) Source # | |
Defined in Features.Output Methods dataOnly :: Feature n d -> OutputShape b Source # nameOnly :: Feature n d -> OutputShape b Source # attrOnly :: Feature n d -> OutputShape b Source # nameData :: Feature n d -> OutputShape b Source # nameAttr :: Feature n d -> OutputShape b Source # | |
| DefineA (e -> d -> c -> b -> Feature n0 a) (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
| DefineA (d -> c -> b -> Feature n0 a) (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Compose | |
| DefineA (c -> b -> Feature n0 a) (Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Compose | |
| DefineA (b -> Feature n0 a) (Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Compose | |
| Define (e -> d -> c -> b -> a) (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Compose | |
| Define (d -> c -> b -> a) (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Compose | |
| Define (c -> b -> a) (Feature n2 c -> Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Compose | |
| Define (b -> a) (Feature n1 b -> Feature n0 a) Source # | |
Defined in Features.Compose | |
| Eval (Feature n2 c -> Feature n1 b -> Feature n0 a) (Feature n2 c, Feature n1 b) (Feature n0 a) Source # | |
| Eval (Feature n1 b -> Feature n0 a) (Feature n1 b) (Feature n0 a) Source # | |
Defined in Features.Compose | |
| Eval (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) (Feature n3 d, Feature n2 c, Feature n1 b) (Feature n0 a) Source # | |
| Eval (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) (Feature n4 e, Feature n3 d, Feature n2 c, Feature n1 b) (Feature n0 a) Source # | |
The type is similar to FeatureN where the Featurename is included
as a Text field. This type is mainly for internal purposes in order to collect
Features of the same type d into a homogeneous container like a .List
featureDataL :: MissingReason -> FeatureData d Source #
Creates a missing FeatureData.
>>>featureDataL (Other "no good reason") :: FeatureData P.IntMkFeatureData (Left (Other "no good reason"))
>>>featureDataL (Other "no good reason") :: FeatureData TextMkFeatureData (Left (Other "no good reason"))
featureDataR :: d -> FeatureData d Source #
Creates a non-missing FeatureData. Since is an instance of
FeatureData, Applicative is also a synonym of for pure.featureDataR
>>>featureDataR "aString"MkFeatureData (Right "aString")>>>featureDataR (1 :: P.Int)MkFeatureData (Right 1)
>>>featureDataR ("aString", (1 :: P.Int))MkFeatureData (Right ("aString",1))
missingBecause :: MissingReason -> FeatureData d Source #
A synonym for featureDataL.
makeFeature :: KnownSymbol name => FeatureData d -> Feature name d Source #
A utility for constructing a from Feature.
Since FeatureDataname is a type, you may need to annotate the type when using this
function.
>>>makeFeature (pure "test") :: Feature "dummy" Text"dummy": MkFeatureData {getFeatureData = Right "test"}
getFeatureData :: FeatureData d -> Either MissingReason d Source #
Unwrap FeatureData.
getFData :: Feature name d -> FeatureData d Source #
Gets the FeatureData from a Feature.
getData :: Feature n d -> Either MissingReason d Source #
A utility for getting the (inner) content of a FeatureData.Feature
getDataN :: FeatureN d -> FeatureData d Source #
Get the data of a FeatureN
nameFeature :: forall name d. KnownSymbol name => Feature name d -> FeatureN d Source #
Feature Definitions
data Definition d where Source #
A Definition can be thought of as a lifted function. Specifically, the
function takes an arbitrary function (currently up to three arguments)
and returns a defineDefintion where the arguments have been lifted to a new domain.
For example, here we take f and lift to to a function of Features.
f :: Int -> String -> Bool f i s | 1 "yes" = True | otherwise = FALSE myFeature :: Definition (Feature A Int -> Feature B String -> Feature C Bool ) myFeature = define f
See for evaluating evalDefintions.
Constructors
| D1 :: (b -> a) -> Definition (f1 b -> f0 a) | |
| D1A :: (b -> f0 a) -> Definition (f1 b -> f0 a) | |
| D2 :: (c -> b -> a) -> Definition (f2 c -> f1 b -> f0 a) | |
| D2A :: (c -> b -> f0 a) -> Definition (f2 c -> f1 b -> f0 a) | |
| D3 :: (d -> c -> b -> a) -> Definition (f3 d -> f2 c -> f1 b -> f0 a) | |
| D3A :: (d -> c -> b -> f0 a) -> Definition (f3 d -> f2 c -> f1 b -> f0 a) | |
| D4 :: (e -> d -> c -> b -> a) -> Definition (f4 e -> f3 d -> f2 c -> f1 b -> f0 a) | |
| D4A :: (e -> d -> c -> b -> f0 a) -> Definition (f4 e -> f3 d -> f2 c -> f1 b -> f0 a) |
class Define inputs def | def -> inputs where Source #
Define (and 'DefineA) provide a means to create new s via
Definition (define). The defineA function takes a single function input
and returns a lifted function. For example,define
f :: Int -> String -> Bool f i s | 1 "yes" = True | otherwise = FALSE myFeature :: Definition (Feature A Int -> Feature B String -> Feature C Bool ) myFeature = define f
The function is similar, except that the return type of the input
function is already lifted. In the example below, an input of defineANothing is
considered a missing state:
f :: Int -> Maybe String -> Feature C Bool f i s | 1 (Just "yes") = pure True | _ (Just _ ) = pure False -- False for any Int and any (Just String) | otherwise = pure $ missingBecause InsufficientData -- missing if no string myFeature :: Definition (Feature A Int -> Feature B String -> Feature C Bool ) myFeature = defineA f
Methods
define :: inputs -> Definition def Source #
Instances
class DefineA inputs def | def -> inputs where Source #
See .Define
Methods
defineA :: inputs -> Definition def Source #
Instances
class Eval def args return | def -> args return where Source #
Evaluate a Definition. Note that (currently), the second argument of eval
is a *tuple* of inputs. For example,
f :: Int -> String -> Bool f i s | 1 "yes" = True | otherwise = FALSE myFeature :: Definition (Feature A Int -> Feature B String -> Feature C Bool ) myFeature = define f a :: Feature A Int a = pure 1 b :: Feature B String b = pure "yes" c = eval myFeature (a, b)
Methods
Arguments
| :: Definition def | |
| -> args | a tuple of arguments to the |
| -> return |
Instances
Adding Attributes to Features
data Attributes Source #
A data type for holding attritbutes of Features. This type and the
are likely to change in future versions.HasAttributes
Constructors
| MkAttributes | |
Fields
| |
Instances
A type to identify a feature's role in a research study.
Constructors
| Outcome | |
| Covariate | |
| Exposure | |
| Competing | |
| Weight | |
| Intermediate | |
| Unspecified |
Instances
| Eq Role Source # | |
| Ord Role Source # | |
| Show Role Source # | |
| Generic Role Source # | |
| ToJSON Role Source # | |
Defined in Features.Output | |
| type Rep Role Source # | |
Defined in Features.Attributes type Rep Role = D1 ('MetaData "Role" "Features.Attributes" "hasklepias-0.17.0-inplace" 'False) ((C1 ('MetaCons "Outcome" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Covariate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exposure" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Competing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Weight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Intermediate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unspecified" 'PrefixI 'False) (U1 :: Type -> Type)))) | |
A type to identify a feature's purpose
Instances
| Eq Purpose Source # | |
| Show Purpose Source # | |
| Generic Purpose Source # | |
| ToJSON Purpose Source # | |
Defined in Features.Output | |
| type Rep Purpose Source # | |
Defined in Features.Attributes type Rep Purpose = D1 ('MetaData "Purpose" "Features.Attributes" "hasklepias-0.17.0-inplace" 'False) (C1 ('MetaCons "MkPurpose" 'PrefixI 'True) (S1 ('MetaSel ('Just "getRole") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Role)) :*: S1 ('MetaSel ('Just "getTags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Text)))) | |
class KnownSymbol name => HasAttributes name d where Source #
A typeclass providing a single method for defining Attributes for a
Feature.
Minimal complete definition
Nothing
Methods
getAttributes :: f name d -> Attributes Source #
emptyAttributes :: Attributes Source #
An empty attributes value.
Arguments
| :: Text | short label |
| -> Text | long label |
| -> [Role] | purpose roles |
| -> [Text] | purpose tags |
| -> Attributes |
Create attributes with just short label, long label, roles, and tags.
emptyPurpose :: Purpose Source #
An empty purpose value.
Exporting Features
data Featureable Source #
Existential type to hold features, which allows for Features to be put into a homogeneous list.
Constructors
| forall d.(Show d, ToJSON d, ShapeOutput d) => MkFeatureable d Attributes |
Instances
| Show Featureable Source # | |
Defined in Features.Featureable Methods showsPrec :: Int -> Featureable -> ShowS # show :: Featureable -> String # showList :: [Featureable] -> ShowS # | |
| ToJSON Featureable Source # | |
Defined in Features.Featureable Methods toJSON :: Featureable -> Value # toEncoding :: Featureable -> Encoding # toJSONList :: [Featureable] -> Value # toEncodingList :: [Featureable] -> Encoding # | |
| ShapeOutput Featureable Source # | |
Defined in Features.Featureable Methods dataOnly :: Featureable -> OutputShape b Source # nameOnly :: Featureable -> OutputShape b Source # attrOnly :: Featureable -> OutputShape b Source # nameData :: Featureable -> OutputShape b Source # nameAttr :: Featureable -> OutputShape b Source # | |
packFeature :: (KnownSymbol n, Show d, ToJSON d, Typeable d, HasAttributes n d) => Feature n d -> Featureable Source #
Pack a feature into a Featurable.
getFeatureableAttrs :: Featureable -> Attributes Source #
Get the Attributes from a Featureable.
data Featureset Source #
A Featureset is a (non-empty) list of Featureable.
Instances
| Show Featureset Source # | |
Defined in Features.Featureset Methods showsPrec :: Int -> Featureset -> ShowS # show :: Featureset -> String # showList :: [Featureset] -> ShowS # | |
| ToJSON Featureset Source # | |
Defined in Features.Featureset Methods toJSON :: Featureset -> Value # toEncoding :: Featureset -> Encoding # toJSONList :: [Featureset] -> Value # toEncodingList :: [Featureset] -> Encoding # | |
| ShapeCohort Featureset Source # | |
Defined in Cohort.Output Methods colWise :: Cohort Featureset -> CohortShape ColumnWise Source # rowWise :: Cohort Featureset -> CohortShape RowWise Source # | |
newtype FeaturesetList Source #
A newtype wrapper for a NonEmpty Featureset.
Constructors
| MkFeaturesetList (NonEmpty Featureset) |
Instances
| Show FeaturesetList Source # | |
Defined in Features.Featureset Methods showsPrec :: Int -> FeaturesetList -> ShowS # show :: FeaturesetList -> String # showList :: [FeaturesetList] -> ShowS # | |
featureset :: NonEmpty Featureable -> Featureset Source #
Constructor of a Featureset.
getFeatureset :: Featureset -> NonEmpty Featureable Source #
Constructor of a Featureset.
getFeaturesetAttrs :: Featureset -> NonEmpty Attributes Source #
Gets a list of Attributes from a Featureset, one Attributes per Featureable.
getFeaturesetList :: FeaturesetList -> NonEmpty Featureset Source #
Constructor of a Featureset.
tpose :: FeaturesetList -> FeaturesetList Source #
Transpose a FeaturesetList
class ToJSON a => ShapeOutput a where Source #
A class that provides methods for transforming some type to an OutputShape.
Methods
dataOnly :: a -> OutputShape b Source #
nameOnly :: a -> OutputShape b Source #
attrOnly :: a -> OutputShape b Source #
nameData :: a -> OutputShape b Source #
nameAttr :: a -> OutputShape b Source #
Instances
| ShapeOutput Featureable Source # | |
Defined in Features.Featureable Methods dataOnly :: Featureable -> OutputShape b Source # nameOnly :: Featureable -> OutputShape b Source # attrOnly :: Featureable -> OutputShape b Source # nameData :: Featureable -> OutputShape b Source # nameAttr :: Featureable -> OutputShape b Source # | |
| (KnownSymbol n, Show d, ToJSON d, Typeable d, HasAttributes n d) => ShapeOutput (Feature n d) Source # | |
Defined in Features.Output Methods dataOnly :: Feature n d -> OutputShape b Source # nameOnly :: Feature n d -> OutputShape b Source # attrOnly :: Feature n d -> OutputShape b Source # nameData :: Feature n d -> OutputShape b Source # nameAttr :: Feature n d -> OutputShape b Source # | |
data OutputShape d Source #
A type used to determine the output shape of a Feature.
Instances
| Show (OutputShape a) Source # | |
Defined in Features.Output Methods showsPrec :: Int -> OutputShape a -> ShowS # show :: OutputShape a -> String # showList :: [OutputShape a] -> ShowS # | |
| ToJSON (OutputShape a) Source # | |
Defined in Features.Output Methods toJSON :: OutputShape a -> Value # toEncoding :: OutputShape a -> Encoding # toJSONList :: [OutputShape a] -> Value # toEncodingList :: [OutputShape a] -> Encoding # | |
Feature definition builders
A collection of pre-defined functions which build common feature definitions used in epidemiologic cohorts.
Arguments
| :: (Intervallic i0 a, Monoid (container (Interval a)), Applicative container, Witherable container) | |
| => Predicate (Event a) | The predicate to filter to Enrollment events (e.g. |
| -> Definition (Feature indexName (Index i0 a) -> Feature eventsName (container (Event a)) -> Feature varName Status) |
Is Enrolled
TODO: describe this
buildContinuousEnrollment Source #
Arguments
| :: (Monoid (container (Interval a)), Monoid (container (Maybe (Interval a))), Applicative container, Witherable container, IntervalSizeable a b) | |
| => (Index i0 a -> AssessmentInterval a) | function which maps index interval to interval in which to assess enrollment |
| -> Predicate (Event a) | The predicate to filter to Enrollment events (e.g. |
| -> b | duration of allowable gap between enrollment intervals |
| -> Definition (Feature indexName (Index i0 a) -> Feature eventsName (container (Event a)) -> Feature prevName Status -> Feature varName Status) |
Continuous Enrollment
TODO: describe this
Arguments
| :: (Intervallic i a, Witherable container) | |
| => (Bool -> outputType) | casting function |
| -> Natural | minimum number of cases |
| -> (Index i a -> AssessmentInterval a) | function to transform a |
| -> ComparativePredicateOf2 (AssessmentInterval a) (Event a) | interval predicate |
| -> Predicate (Event a) | a predicate on events |
| -> Definition (Feature indexName (Index i a) -> Feature eventsName (container (Event a)) -> Feature varName outputType) |
Do N events relating to the AssessmentInterval in some way the satisfy
the given predicate?
Arguments
| :: (Intervallic i a, Witherable container) | |
| => Natural | minimum number of cases |
| -> (Index i a -> AssessmentInterval a) | function to transform a |
| -> ComparativePredicateOf2 (AssessmentInterval a) (Event a) | interval predicate |
| -> Predicate (Event a) | a predicate on events |
| -> Definition (Feature indexName (Index i a) -> Feature eventsName (container (Event a)) -> Feature varName Bool) |
buildNofXBinary :: (Intervallic i a, Witherable container) => Natural -> (Index i a -> AssessmentInterval a) -> ComparativePredicateOf2 (AssessmentInterval a) (Event a) -> Predicate (Event a) -> Definition (Feature indexName (Index i a) -> Feature eventsName (container (Event a)) -> Feature varName Binary) Source #
buildNofXBinaryConcurBaseline Source #
Arguments
| :: (Intervallic i0 a, Witherable t, IntervalSizeable a b, Baseline i0 a) | |
| => Natural | minimum number of events. |
| -> b | duration of baseline (passed to |
| -> Predicate (Event a) | |
| -> Definition (Feature indexName (Index i0 a) -> Feature eventsName (t (Event a)) -> Feature varName Binary) |
buildNofXBinary specialized to filter to events that concur
with an AssessmentInterval created by makeBaselineFromIndex of
a specified duration and a provided Predicate.
buildNofConceptsBinaryConcurBaseline Source #
Arguments
| :: (Intervallic i0 a, Witherable t, IntervalSizeable a b, Baseline i0 a) | |
| => Natural | minimum number of events. |
| -> b | duration of baseline (passed to |
| -> [Text] | list of |
| -> Definition (Feature indexName (Index i0 a) -> Feature eventsName (t (Event a)) -> Feature varName Bool) |
buildNofXBinary specialized to filter to events that concur
with an AssessmentInterval created by makeBaselineFromIndex of
a specified duration and that have a given set of Concepts.
Arguments
| :: (Intervallic i a, IntervalSizeable a b, IntervalCombinable i a, Witherable container) | |
| => (Bool -> outputType) | |
| -> Natural | the minimum number of gaps |
| -> b | the minimum duration of a gap |
| -> (Index i a -> AssessmentInterval a) | |
| -> ComparativePredicateOf2 (AssessmentInterval a) (Event a) | |
| -> Predicate (Event a) | |
| -> Definition (Feature indexName (Index i a) -> Feature eventsName (container (Event a)) -> Feature varName outputType) |
Are there N gaps of at least the given duration between any pair of events
that relate to the AssessmentInterval by the given relation and the
satisfy the given predicate?
Arguments
| :: (Intervallic i a, IntervalSizeable a b, IntervalCombinable i a, Witherable container) | |
| => Natural | the minimum number of gaps |
| -> b | the minimum duration of a gap |
| -> (Index i a -> AssessmentInterval a) | |
| -> ComparativePredicateOf2 (AssessmentInterval a) (Event a) | |
| -> Predicate (Event a) | |
| -> Definition (Feature indexName (Index i a) -> Feature eventsName (container (Event a)) -> Feature varName Bool) |
buildNofXWithGap specialized to return Bool.
buildNofXWithGapBinary Source #
Arguments
| :: (Intervallic i a, IntervalSizeable a b, IntervalCombinable i a, Witherable container) | |
| => Natural | the minimum number of gaps |
| -> b | the minimum duration of a gap |
| -> (Index i a -> AssessmentInterval a) | |
| -> ComparativePredicateOf2 (AssessmentInterval a) (Event a) | |
| -> Predicate (Event a) | |
| -> Definition (Feature indexName (Index i a) -> Feature eventsName (container (Event a)) -> Feature varName Binary) |
buildNofXWithGap specialized to return Binary.
Arguments
| :: (Intervallic i a, IntervalSizeable a b, Witherable container) | |
| => (Index i a -> AssessmentInterval a) | function to transform a |
| -> ComparativePredicateOf2 (AssessmentInterval a) (Event a) | interval predicate |
| -> Predicate (Event a) | a predicate on events |
| -> Definition (Feature indexName (Index i a) -> Feature eventsName (container (Event a)) -> Feature varName [(EventTime b, Count)]) |
Do N events relating to the AssessmentInterval in some way the satisfy
the given predicate?
Utilities for defining Features from Events
Much of logic needed to define features from events depends on the interval-algebra library. Its main functions and types are re-exported in Hasklepias, but the documentation can be found on hackage.
Container predicates
isNotEmpty :: [a] -> Bool Source #
Is the input list empty?
Does Events have at least n events with any of the Concept in x.
anyGapsWithinAtLeastDuration Source #
Arguments
| :: (IntervalSizeable a b, Intervallic i0 a, IntervalCombinable i1 a, Monoid (t (Interval a)), Monoid (t (Maybe (Interval a))), Applicative t, Witherable t) | |
| => b | duration of gap |
| -> i0 a | within this interval |
| -> t (i1 a) | |
| -> Bool |
Within a provided spanning interval, are there any gaps of at least the specified duration among the input intervals?
allGapsWithinLessThanDuration Source #
Arguments
| :: (IntervalSizeable a b, Intervallic i0 a, IntervalCombinable i1 a, Monoid (t (Interval a)), Monoid (t (Maybe (Interval a))), Applicative t, Witherable t) | |
| => b | duration of gap |
| -> i0 a | within this interval |
| -> t (i1 a) | |
| -> Bool |
Within a provided spanning interval, are all gaps less than the specified duration among the input intervals?
>>>allGapsWithinLessThanDuration 30 (beginerval 100 (0::Int)) [beginerval 5 (-1), beginerval 99 10]True
Finding occurrences of concepts
Arguments
| :: Filterable f | |
| => (f (Event a) -> Maybe (Event a)) | function used to select a single event |
| -> [Text] | |
| -> f (Event a) | |
| -> Maybe (Event a) |
Filter Events to a single , based on a provided function,
with the provided concepts. For example, see Maybe EventfirstConceptOccurrence and
lastConceptOccurrence.
firstConceptOccurrence :: Witherable f => [Text] -> f (Event a) -> Maybe (Event a) Source #
Reshaping containers
allPairs :: Applicative f => f a -> f b -> f (a, b) Source #
Generate all pair-wise combinations from two lists.
splitByConcepts :: Filterable f => [Text] -> [Text] -> f (Event a) -> (f (Event a), f (Event a)) Source #
Split an Events a into a pair of Events a. The first element contains
events have any of the concepts in the first argument, similarly for the
second element.
Create filters
Arguments
| :: Filterable f | |
| => [Text] | the list of concepts by which to filter |
| -> f (Event a) | |
| -> f (Event a) |
Filter Events to those that have any of the provided concepts.
makePairedFilter :: Ord a => ComparativePredicateOf2 (i0 a) (PairedInterval b a) -> i0 a -> (b -> Bool) -> [PairedInterval b a] -> [PairedInterval b a] Source #
Manipulating Dates
monthFromDay :: Day -> MonthOfYear Source #
Gets the MonthOfDay from a Day.
dayOfMonthFromDay :: Day -> DayOfMonth Source #
Gets the DayOfMonth from a Day.
Functions for manipulating intervals
Arguments
| :: (Intervallic i a, IntervalSizeable a b) | |
| => b | lookback duration |
| -> i a | |
| -> Interval a |
Creates a new Interval of a provided lookback duration ending at the
begin of the input interval.
>>>lookback 4 (beginerval 10 (1 :: Int))(-3, 1)
Arguments
| :: (Intervallic i a, IntervalSizeable a b) | |
| => b | lookahead duration |
| -> i a | |
| -> Interval a |
Creates a new Interval of a provided lookahead duration beginning at the
end of the input interval.
>>>lookahead 4 (beginerval 1 (1 :: Int))(2, 6)
Misc functions
computeAgeAt :: Day -> Day -> Integer Source #
Compute the "age" in years between two calendar days. The difference between the days is rounded down.
pairGaps :: (Intervallic i a, IntervalSizeable a b, IntervalCombinable i a) => [i a] -> [Maybe b] Source #
Gets the durations of gaps (via 'IntervalAlgebra.(><)') between all pairs of the input.
type Def d = Definition d Source #
Type synonym for Definition.
newtype Occurrence what when Source #
A type containing the time and when something occurred
Constructors
| MkOccurrence (what, EventTime when) |
Instances
makeOccurrence :: OccurrenceReason what => what -> EventTime b -> Occurrence what b Source #
Create an Occurrence
getOccurrenceReason :: Occurrence what b -> what Source #
Get the reason for an Occurrence.
getOccurrenceTime :: Occurrence what b -> EventTime b Source #
Get the time of an Occurrence.
data CensoringReason cr or Source #
Sum type for possible censoring and outcome reasons, including administrative censoring.
Constructors
| AdminCensor | |
| C cr | |
| O or |
Instances
class (Ord a, Show a) => OccurrenceReason a Source #
A simple typeclass for making a type a "reason" for an event.
data CensoredOccurrence censors outcomes b Source #
A type to represent censored Occurrence.
Constructors
| MkCensoredOccurrence | |
Fields
| |
Instances
adminCensor :: EventTime b -> CensoredOccurrence c o b Source #
Creates an administratively censored occurrence.
Specifying and building cohorts
Defining Cohorts
A subject is just a pair of ID and data.
newtype Population d Source #
A population is a list of sSubject
Constructors
| MkPopulation [Subject d] |
Instances
| Functor Population Source # | |
Defined in Cohort.Core Methods fmap :: (a -> b) -> Population a -> Population b # (<$) :: a -> Population b -> Population a # | |
| Eq d => Eq (Population d) Source # | |
Defined in Cohort.Core | |
| Show d => Show (Population d) Source # | |
Defined in Cohort.Core Methods showsPrec :: Int -> Population d -> ShowS # show :: Population d -> String # showList :: [Population d] -> ShowS # | |
| Generic (Population d) Source # | |
Defined in Cohort.Core Associated Types type Rep (Population d) :: Type -> Type # | |
| FromJSON d => FromJSON (Population d) Source # | |
Defined in Cohort.Core Methods parseJSON :: Value -> Parser (Population d) # parseJSONList :: Value -> Parser [Population d] # | |
| type Rep (Population d) Source # | |
Defined in Cohort.Core type Rep (Population d) = D1 ('MetaData "Population" "Cohort.Core" "hasklepias-0.17.0-inplace" 'True) (C1 ('MetaCons "MkPopulation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Subject d]))) | |
An observational unit is what a subject may be transformed into.
Instances
| Eq d => Eq (ObsUnit d) Source # | |
| Show d => Show (ObsUnit d) Source # | |
| Generic (ObsUnit d) Source # | |
| ToJSON d => ToJSON (ObsUnit d) Source # | |
Defined in Cohort.Output | |
| type Rep (ObsUnit d) Source # | |
Defined in Cohort.Core type Rep (ObsUnit d) = D1 ('MetaData "ObsUnit" "Cohort.Core" "hasklepias-0.17.0-inplace" 'False) (C1 ('MetaCons "MkObsUnit" 'PrefixI 'True) (S1 ('MetaSel ('Just "obsID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ID) :*: S1 ('MetaSel ('Just "obsData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d))) | |
newtype CohortData d Source #
A container for CohortData
Constructors
| MkCohortData | |
Fields
| |
Instances
| Eq d => Eq (CohortData d) Source # | |
Defined in Cohort.Core | |
| Show d => Show (CohortData d) Source # | |
Defined in Cohort.Core Methods showsPrec :: Int -> CohortData d -> ShowS # show :: CohortData d -> String # showList :: [CohortData d] -> ShowS # | |
| Generic (CohortData d) Source # | |
Defined in Cohort.Core Associated Types type Rep (CohortData d) :: Type -> Type # | |
| ToJSON d => ToJSON (CohortData d) Source # | |
Defined in Cohort.Output Methods toJSON :: CohortData d -> Value # toEncoding :: CohortData d -> Encoding # toJSONList :: [CohortData d] -> Value # toEncodingList :: [CohortData d] -> Encoding # | |
| type Rep (CohortData d) Source # | |
Defined in Cohort.Core type Rep (CohortData d) = D1 ('MetaData "CohortData" "Cohort.Core" "hasklepias-0.17.0-inplace" 'True) (C1 ('MetaCons "MkCohortData" 'PrefixI 'True) (S1 ('MetaSel ('Just "getObsData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ObsUnit d]))) | |
A cohort is a list of observational units along with
regarding the number of subjects excluded by the AttritionInfo. Criteria
Constructors
| MkCohort (Maybe AttritionInfo, CohortData d) |
Instances
| Eq d => Eq (Cohort d) Source # | |
| Show d => Show (Cohort d) Source # | |
| Generic (Cohort d) Source # | |
| ToJSON d => ToJSON (Cohort d) Source # | |
Defined in Cohort.Output | |
| type Rep (Cohort d) Source # | |
Defined in Cohort.Core type Rep (Cohort d) = D1 ('MetaData "Cohort" "Cohort.Core" "hasklepias-0.17.0-inplace" 'True) (C1 ('MetaCons "MkCohort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AttritionInfo, CohortData d)))) | |
data CohortSpec d1 d0 Source #
A cohort specification consist of two functions: one that transforms a subject's
input data into a and another that transforms a subject's input data
into the desired return type.Criteria
newtype AttritionInfo Source #
A type which collects the counts of subjects included or excluded.
Constructors
| MkAttritionInfo (NonEmpty (CohortStatus, Natural)) |
Instances
specifyCohort :: (d1 -> Criteria) -> (d1 -> d0) -> CohortSpec d1 d0 Source #
Creates a .CohortSpec
makeObsUnitFeatures :: (d1 -> d0) -> Subject d1 -> ObsUnit d0 Source #
evalCohort :: CohortSpec d1 d0 -> Population d1 -> Cohort d0 Source #
Evaluates a on a CohortSpec.Population
getCohortIDs :: Cohort d -> [ID] Source #
Get IDs from a cohort.
getCohortData :: Cohort d -> [d] Source #
Get data from a cohort.
getAttritionInfo :: Cohort d -> Maybe AttritionInfo Source #
Gets the attrition info from a cohort
Index
An Index is an interval of time from which the assessment intervals for an
observational unit may be derived. Assessment intervals (encoded in the type
AssessmentInterval) are intervals of time during which features are evaluated.
An Index is a wrapper for an Intervallic used to indicate that a particular
interval is considered an index interval to which other intervals will be compared.
Instances
| Functor i => Functor (Index i) Source # | |
| Intervallic i a => Intervallic (Index i) a Source # | |
Defined in Cohort.Index Methods getInterval :: Index i a -> Interval a # setInterval :: Index i a -> Interval a -> Index i a # | |
| Eq (i a) => Eq (Index i a) Source # | |
| Show (i a) => Show (Index i a) Source # | |
| Generic (Index i a) Source # | |
| (Intervallic i a, ToJSON (i a)) => ToJSON (Index i a) Source # | |
Defined in Cohort.Index | |
| type Rep (Index i a) Source # | |
Defined in Cohort.Index | |
Assessment Intervals
The assessment intervals provided are:
Baseline: an interval which eithermeetsorprecedesindex. Covariates are typically assessed during baseline intervals. A cohort's specification may include multiple baseline intervals, as different features may require different baseline intervals. For example, one feature may use a baseline interval of 365 days prior to index, while another uses a baseline interval of 90 days before index up to 30 days before index.Followup: an interval which isstartedBy,metBy, orafteranIndex. Outcomes are typically assessed during followup intervals. Similar toBaseline, a cohort's specification may include multiple followup intervals, as different features may require different followup intervals.
In future versions, one subject may have multiple values for an Index
corresponding to unique ObsUnit. That is, there is a 1-to-1 map between
index values and observational units, but there may be a 1-to-many map from
subjects to indices.
While users are protected from forming invalid assessment intervals, they still need to carefully consider how to filter events based on the assessment interval. Consider the following data:
_ <- Index (15, 16)
---------- <- Baseline (5, 15)
--- <- A (1, 4)
--- <- B (2, 5)
--- <- C (4, 7)
--- <- D (5, 8)
--- <- E (8, 11)
--- <- F (12, 15)
--- <- G (14, 17)
___ <- H (17, 20)
|----|----|----|----|
0 10 20
We have index, baseline, and 8 events (A-H). If Baseline is our assessment interval,
then the events concuring (i.e. not disjoint) with Baseline are C-G. While C-F
probably make sense to use in deriving some covariate, what about G? The event G
begins during baseline but ends after index. If you want, for example, to know
how many events started during baseline, then you’d want to include G in your
filter (using concur). But if you wanted to know the durations
of events enclosed by baseline, then you wouldn’t want to filter using concur
and instead perhaps use enclosedBy.
data BaselineInterval a Source #
A type to contain baseline intervals. See the Baseline typeclass for methods
to create values of this type.
Instances
class Intervallic i a => Baseline i a where Source #
Provides functions for creating a BaselineInterval from an Index. The
baseline function should satify:
- Meets
relate(baselined i) i =Meets
The baselineBefore function should satisfy:
- Before
relate(baselineBefores d i) i =Before
>>>import Cohort.Index>>>import IntervalAlgebra>>>x = makeIndex (beginerval 1 10)>>>b =baseline 10 x>>>b>>>relate b xMkBaselineInterval (0, 10) Meets
>>>import Cohort.Index>>>import IntervalAlgebra>>>x = makeIndex (beginerval 1 10)>>>b = baselineBefore 2 4 x>>>b>>>relate b xMkBaselineInterval (4, 8) Before
Minimal complete definition
Nothing
Methods
Arguments
| :: IntervalSizeable a b | |
| => b | duration of baseline |
| -> Index i a | the |
| -> BaselineInterval a |
Creates a BaselineInterval of the given duration that Meets
the Index interval.
Arguments
| :: IntervalSizeable a b | |
| => b | duration to shift back |
| -> b | duration of baseline |
| -> Index i a | the |
| -> BaselineInterval a |
Creates a BaselineInterval of the given duration that precedes
the Index interval.
Instances
| Ord a => Baseline Interval a Source # | |
Defined in Cohort.AssessmentIntervals Methods baseline :: IntervalSizeable a b => b -> Index Interval a -> BaselineInterval a Source # baselineBefore :: IntervalSizeable a b => b -> b -> Index Interval a -> BaselineInterval a Source # | |
data FollowupInterval a Source #
A type to contain followup intervals. See the Followup typeclass for methods
to create values of this type.
Instances
class Intervallic i a => Followup i a where Source #
Provides functions for creating a FollowupInterval from an Index. The
followup function should satify:
- StartedBy
relate(followupd i) i =StartedBy
The followupMetBy function should satisfy:
- MetBy
relate(followupMetByd i) i =MetBy
The followupAfter function should satisfy:
- After
relate(followupAfters d i) i =After
>>>import Cohort.Index>>>import IntervalAlgebra>>>x = makeIndex (beginerval 1 10)>>>f = followup 10 x>>>f>>>relate f xMkFollowupInterval (10, 20) StartedBy
Note the consequence of providing a duration less than or equal to the duration
of the index: a moment is added to the duration, so that the
end of the FollowupInterval is greater than the end of the Index.
>>>import Cohort.Index>>>import IntervalAlgebra>>>x = makeIndex (beginerval 1 10)>>>f = followup 1 x>>>f>>>relate f xMkFollowupInterval (10, 12) StartedBy
>>>import Cohort.Index>>>import IntervalAlgebra>>>x = makeIndex (beginerval 1 10)>>>f = followupMetBy 9 x>>>f>>>relate f xMkFollowupInterval (11, 20) MetBy
>>>import Cohort.Index>>>import IntervalAlgebra>>>x = makeIndex (beginerval 1 10)>>>f = followupAfter 1 9 x>>>f>>>relate f xMkFollowupInterval (12, 21) After
Minimal complete definition
Nothing
Methods
Arguments
| :: (IntervalSizeable a b, Intervallic i a) | |
| => b | duration of followup |
| -> Index i a | the |
| -> FollowupInterval a |
Arguments
| :: (IntervalSizeable a b, Intervallic i a) | |
| => b | duration of followup |
| -> Index i a | the |
| -> FollowupInterval a |
Arguments
| :: (IntervalSizeable a b, Intervallic i a) | |
| => b | duration add between the end of index and begin of followup |
| -> b | duration of followup |
| -> Index i a | the |
| -> FollowupInterval a |
Instances
| Ord a => Followup Interval a Source # | |
Defined in Cohort.AssessmentIntervals Methods followup :: (IntervalSizeable a b, Intervallic Interval a) => b -> Index Interval a -> FollowupInterval a Source # followupMetBy :: (IntervalSizeable a b, Intervallic Interval a) => b -> Index Interval a -> FollowupInterval a Source # followupAfter :: (IntervalSizeable a b, Intervallic Interval a) => b -> b -> Index Interval a -> FollowupInterval a Source # | |
data AssessmentInterval a Source #
A data type that contains variants of intervals during which assessment may occur.
Instances
makeBaselineFromIndex :: (Baseline i a, IntervalSizeable a b) => b -> Index i a -> AssessmentInterval a Source #
Creates an AssessmentInterval using the baseline function.
>>>import Cohort.Index>>>x = makeIndex $ beginerval 1 10>>>makeBaselineFromIndex 10 xBl (MkBaselineInterval (0, 10))
makeBaselineBeforeIndex :: (Baseline i a, IntervalSizeable a b) => b -> b -> Index i a -> AssessmentInterval a Source #
Creates an AssessmentInterval using the baselineBefore function.
>>>import Cohort.Index>>>x = makeIndex $ beginerval 1 10>>>makeBaselineBeforeIndex 2 10 xBl (MkBaselineInterval (-2, 8))
makeFollowupFromIndex :: (Followup i a, IntervalSizeable a b) => b -> Index i a -> AssessmentInterval a Source #
Creates an AssessmentInterval using the followup function.
>>>import Cohort.Index>>>x = makeIndex $ beginerval 1 10>>>makeFollowupFromIndex 10 xFl (MkFollowupInterval (10, 20))
makeFollowupMeetingIndex :: (Followup i a, IntervalSizeable a b) => b -> Index i a -> AssessmentInterval a Source #
Creates an AssessmentInterval using the followupMetBy function.
>>>import Cohort.Index>>>x = makeIndex $ beginerval 1 10>>>makeFollowupMeetingIndex 10 xFl (MkFollowupInterval (11, 21))
makeFollowupAfterIndex :: (Followup i a, IntervalSizeable a b) => b -> b -> Index i a -> AssessmentInterval a Source #
Creates an AssessmentInterval using the followupAfter function.
>>>import Cohort.Index>>>x = makeIndex $ beginerval 1 10>>>makeFollowupAfterIndex 10 10 xFl (MkFollowupInterval (21, 31))
Criteria
A type that is simply a 'FeatureN Status', that is, a feature that
identifies whether to or Include a subject.Exclude
Instances
A nonempty collection of paired with a CriterionNatural number.
Constructors
| MkCriteria | |
Fields
| |
Defines the return type for indicating whether to include or
exclude a subject.Criterion
data CohortStatus Source #
Defines subject's diposition in a cohort either included or which criterion
they were excluded by. See for evaluating a checkCohortStatus
to determine CohortStatus.Criteria
Constructors
| Included | |
| ExcludedBy (Natural, Text) |
Instances
excludeIf :: Bool -> Status Source #
Helper to convert a Bool to a Status
>>>excludeIf True>>>excludeIf FalseExclude Include
includeIf :: Bool -> Status Source #
Helper to convert a Bool to a Status
>>>includeIf True>>>includeIf FalseInclude Exclude
initStatusInfo :: Criteria -> NonEmpty CohortStatus Source #
Initializes a container of from a CohortStatus. This can be used
to collect generate all the possible Exclusion/Inclusion reasons. Criteria
checkCohortStatus :: Criteria -> CohortStatus Source #
Converts a subject's to a Criteria. The status is set
to CohortStatus if none of the Included have a status of Criterion.Exclude
Cohort I/O
Input
parsePopulationLines :: (FromJSON a, Show a, IntervalSizeable a b) => ByteString -> ([ParseError], Population (Events a)) Source #
Parse Event Int from json lines.
parsePopulationIntLines :: ByteString -> ([ParseError], Population (Events Int)) Source #
Parse Event Int from json lines.
parsePopulationDayLines :: ByteString -> ([ParseError], Population (Events Day)) Source #
Parse Event Day from json lines.
newtype ParseError Source #
Contains the line number and error message.
Constructors
| MkParseError (Natural, Text) |
Instances
| Eq ParseError Source # | |
Defined in Cohort.Input | |
| Show ParseError Source # | |
Defined in Cohort.Input Methods showsPrec :: Int -> ParseError -> ShowS # show :: ParseError -> String # showList :: [ParseError] -> ShowS # | |
Output
data CohortShape d Source #
A type used to determine the output shape of a Cohort.
Instances
| Show d => Show (CohortShape d) Source # | |
Defined in Cohort.Output Methods showsPrec :: Int -> CohortShape d -> ShowS # show :: CohortShape d -> String # showList :: [CohortShape d] -> ShowS # | |
class ShapeCohort d where Source #
Provides methods for reshaping a Cohort to a CohortShape.
Methods
colWise :: Cohort d -> CohortShape ColumnWise Source #
rowWise :: Cohort d -> CohortShape RowWise Source #
Instances
| ShapeCohort Featureset Source # | |
Defined in Cohort.Output Methods colWise :: Cohort Featureset -> CohortShape ColumnWise Source # rowWise :: Cohort Featureset -> CohortShape RowWise Source # | |
toJSONCohortShape :: CohortShape shape -> Value Source #
Maps CohortShape into an Aeson Value. TODO: implement Generic and ToJSON instance of CohortShape directly.
Creating an executable cohort application
Arguments
| :: (FromJSON a, Show a, IntervalSizeable a b, ToJSON d0, ShapeCohort d0) | |
| => String | cohort name |
| -> String | app version |
| -> (Cohort d0 -> CohortShape shape) | a function which specifies the output shape |
| -> [CohortSpec (Events a) d0] | a list of cohort specifications |
| -> IO () |
Make a command line cohort building application.
Statistical Types
module Stype.Numeric
module Stype.Categorical
module Stype.Aeson
Rexported Functions and modules
module Hasklepias.Reexports
module Hasklepias.ReexportsUnsafe