hasklepias-0.17.0: embedded DSL for defining epidemiologic cohorts
Copyright(c) NoviSci Inc 2020
LicenseBSD3
Maintainerbsaul@novisci.com
Safe HaskellNone
LanguageHaskell2010

Hasklepias

Description

See the examples folder and manual for further documentation.

Synopsis

Events

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

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 #

Get 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.

toConceptEventOf :: (Show a, Ord a) => [Concept] -> Event a -> ConceptEvent a Source #

Creates a new ConceptEvent from an Event 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 Contexts

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 

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

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.Core

context :: Domain -> Concepts -> Context Source #

Smart contructor for Context type

Creates Context from a list of Concepts. At this time, the facts and source are both set to Nothing.

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 Concepts Source #

Concepts is a Set of Concepts.

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.Core

getConcepts :: Concepts -> Set Concept Source #

Unwrap the Concepts newtype.

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

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.Core

HasConcept (Event a) Source # 
Instance details

Defined in EventData.Core

data Source Source #

Instances

Instances details
Eq Source Source # 
Instance details

Defined in EventData.Context

Methods

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

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

Show Source Source # 
Instance details

Defined in EventData.Context

Event Domains

data Domain Source #

Defines the available domains.

Instances

Instances details
Eq Domain Source # 
Instance details

Defined in EventData.Context.Domain

Methods

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

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

Show Domain Source # 
Instance details

Defined in EventData.Context.Domain

Generic Domain Source # 
Instance details

Defined in EventData.Context.Domain

Associated Types

type Rep Domain :: Type -> Type #

Methods

from :: Domain -> Rep Domain x #

to :: Rep Domain x -> Domain #

FromJSON Domain Source # 
Instance details

Defined in EventData.Aeson

type Rep Domain Source # 
Instance details

Defined in EventData.Context.Domain

data DemographicsInfo Source #

information of a demographic fact

data DemographicsField Source #

fields available in a demographic fact

Instances

Instances details
Eq DemographicsField Source # 
Instance details

Defined in EventData.Context.Domain.Demographics

Show DemographicsField Source # 
Instance details

Defined in EventData.Context.Domain.Demographics

Generic DemographicsField Source # 
Instance details

Defined in EventData.Context.Domain.Demographics

Associated Types

type Rep DemographicsField :: Type -> Type #

FromJSON DemographicsField Source # 
Instance details

Defined in EventData.Context.Domain.Demographics

type Rep DemographicsField Source # 
Instance details

Defined in EventData.Context.Domain.Demographics

type Rep DemographicsField = D1 ('MetaData "DemographicsField" "EventData.Context.Domain.Demographics" "hasklepias-0.17.0-inplace" 'False) ((((C1 ('MetaCons "BirthYear" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BirthDate" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Race" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RaceCodes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Gender" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Zipcode" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "County" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CountyFIPS" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "State" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Ethnicity" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Region" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "UrbanRural" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GeoPctAmIndian" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GeoPctAsian" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GeoPctBlack" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GeoPctHispanic" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "GeoPctMutli" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GeoPctOther" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GeoPctWhite" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "GeoType" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GeoAdiStateRank" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GeoAdiNatRank" 'PrefixI 'False) (U1 :: Type -> Type))))))

newtype EnrollmentFacts Source #

An enrollment fact

Constructors

EnrollmentFacts 

Fields

Instances

Instances details
Eq EnrollmentFacts Source # 
Instance details

Defined in EventData.Context.Domain.Enrollment

Show EnrollmentFacts Source # 
Instance details

Defined in EventData.Context.Domain.Enrollment

Generic EnrollmentFacts Source # 
Instance details

Defined in EventData.Context.Domain.Enrollment

Associated Types

type Rep EnrollmentFacts :: Type -> Type #

FromJSON EnrollmentFacts Source # 
Instance details

Defined in EventData.Context.Domain.Enrollment

type Rep EnrollmentFacts Source # 
Instance details

Defined in EventData.Context.Domain.Enrollment

type Rep EnrollmentFacts = D1 ('MetaData "EnrollmentFacts" "EventData.Context.Domain.Enrollment" "hasklepias-0.17.0-inplace" 'True) (C1 ('MetaCons "EnrollmentFacts" 'PrefixI 'True) (S1 ('MetaSel ('Just "_plan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ())))

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

containsConcepts :: [Text] -> Predicate (Event a) Source #

Creates a predicate to check that an Event contains a set of Concepts.

class Predicatable a where Source #

Provides methods for composing predicate functions (i.e. a -> Bool) or Predicates by conjunction or disjunction.

Methods

(|||) :: a -> a -> a Source #

(&&&) :: a -> a -> a Source #

Instances

Instances details
Predicatable (Predicate a) Source # 
Instance details

Defined in EventData.Predicates

Predicatable (a -> Bool) Source # 
Instance details

Defined in EventData.Predicates

Methods

(|||) :: (a -> Bool) -> (a -> Bool) -> a -> Bool Source #

(&&&) :: (a -> Bool) -> (a -> Bool) -> 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

previewDemoInfo :: Domain -> Maybe Text Source #

Preview demographics information from a domain

previewBirthYear :: Domain -> Maybe Year Source #

Preview birth year from a domain

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

generateEventsInt :: Int -> IO [Event Int] Source #

Generate n Event Int

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 Left of an Either, while the data d is contained in the Either's Right.

To construct a successful value, use featureDataR. A missing value can be constructed with featureDataL or its synonym missingBecause.

Instances

Instances details
Monad FeatureData Source # 
Instance details

Defined in Features.Compose

Methods

(>>=) :: FeatureData a -> (a -> FeatureData b) -> FeatureData b #

(>>) :: FeatureData a -> FeatureData b -> FeatureData b #

return :: a -> FeatureData a #

Functor FeatureData Source #

Transform (fmap) FeatureData of one type to another.

>>> x = featureDataR (1 :: P.Int)
>>> :type x
>>> :type ( fmap show x )
x :: FeatureData Int
( fmap show x ) :: FeatureData String

Note that Left values are carried along while the type changes:

>>> x = ( featureDataL InsufficientData ) :: FeatureData P.Int
>>> :type x
>>> x
>>> :type ( fmap show x )
>>> fmap show x
x :: FeatureData Int
MkFeatureData {getFeatureData = Left InsufficientData}
( fmap show x ) :: FeatureData String
MkFeatureData {getFeatureData = Left InsufficientData}
Instance details

Defined in Features.Compose

Methods

fmap :: (a -> b) -> FeatureData a -> FeatureData b #

(<$) :: a -> FeatureData b -> FeatureData a #

Applicative FeatureData Source # 
Instance details

Defined in Features.Compose

Methods

pure :: a -> FeatureData a #

(<*>) :: FeatureData (a -> b) -> FeatureData a -> FeatureData b #

liftA2 :: (a -> b -> c) -> FeatureData a -> FeatureData b -> FeatureData c #

(*>) :: FeatureData a -> FeatureData b -> FeatureData b #

(<*) :: FeatureData a -> FeatureData b -> FeatureData a #

Foldable FeatureData Source # 
Instance details

Defined in Features.Compose

Methods

fold :: Monoid m => FeatureData m -> m #

foldMap :: Monoid m => (a -> m) -> FeatureData a -> m #

foldMap' :: Monoid m => (a -> m) -> FeatureData a -> m #

foldr :: (a -> b -> b) -> b -> FeatureData a -> b #

foldr' :: (a -> b -> b) -> b -> FeatureData a -> b #

foldl :: (b -> a -> b) -> b -> FeatureData a -> b #

foldl' :: (b -> a -> b) -> b -> FeatureData a -> b #

foldr1 :: (a -> a -> a) -> FeatureData a -> a #

foldl1 :: (a -> a -> a) -> FeatureData a -> a #

toList :: FeatureData a -> [a] #

null :: FeatureData a -> Bool #

length :: FeatureData a -> Int #

elem :: Eq a => a -> FeatureData a -> Bool #

maximum :: Ord a => FeatureData a -> a #

minimum :: Ord a => FeatureData a -> a #

sum :: Num a => FeatureData a -> a #

product :: Num a => FeatureData a -> a #

Traversable FeatureData Source # 
Instance details

Defined in Features.Compose

Methods

traverse :: Applicative f => (a -> f b) -> FeatureData a -> f (FeatureData b) #

sequenceA :: Applicative f => FeatureData (f a) -> f (FeatureData a) #

mapM :: Monad m => (a -> m b) -> FeatureData a -> m (FeatureData b) #

sequence :: Monad m => FeatureData (m a) -> m (FeatureData a) #

Eq d => Eq (FeatureData d) Source # 
Instance details

Defined in Features.Compose

Show d => Show (FeatureData d) Source # 
Instance details

Defined in Features.Compose

Generic (FeatureData d) Source # 
Instance details

Defined in Features.Compose

Associated Types

type Rep (FeatureData d) :: Type -> Type #

Methods

from :: FeatureData d -> Rep (FeatureData d) x #

to :: Rep (FeatureData d) x -> FeatureData d #

ToJSON d => ToJSON (FeatureData d) Source # 
Instance details

Defined in Features.Output

Eval (FeatureData b -> FeatureData a) (FeatureData b) (FeatureData a) Source # 
Instance details

Defined in Features.Compose

DefineA (e -> d -> c -> b -> FeatureData a) (FeatureData e -> FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Methods

defineA :: (e -> d -> c -> b -> FeatureData a) -> Definition (FeatureData e -> FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source #

DefineA (d -> c -> b -> FeatureData a) (FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Methods

defineA :: (d -> c -> b -> FeatureData a) -> Definition (FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source #

DefineA (c -> b -> FeatureData a) (FeatureData c -> FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Methods

defineA :: (c -> b -> FeatureData a) -> Definition (FeatureData c -> FeatureData b -> FeatureData a) Source #

DefineA (b -> FeatureData a) (FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Define (e -> d -> c -> b -> a) (FeatureData e -> FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (e -> d -> c -> b -> a) -> Definition (FeatureData e -> FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source #

Define (d -> c -> b -> a) (FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (d -> c -> b -> a) -> Definition (FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source #

Define (c -> b -> a) (FeatureData c -> FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (c -> b -> a) -> Definition (FeatureData c -> FeatureData b -> FeatureData a) Source #

Define (b -> a) (FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (b -> a) -> Definition (FeatureData b -> FeatureData a) Source #

Eval (FeatureData c -> FeatureData b -> FeatureData a) (FeatureData c, FeatureData b) (FeatureData a) Source # 
Instance details

Defined in Features.Compose

Eval (FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) (FeatureData d, FeatureData c, FeatureData b) (FeatureData a) Source # 
Instance details

Defined in Features.Compose

type Rep (FeatureData d) Source # 
Instance details

Defined in Features.Compose

type Rep (FeatureData d) = D1 ('MetaData "FeatureData" "Features.Compose" "hasklepias-0.17.0-inplace" 'True) (C1 ('MetaCons "MkFeatureData" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFeatureData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either MissingReason d))))

data MissingReason Source #

Defines the reasons that a FeatureData value may be missing. Can be used to indicate the reason that a Feature's data was unable to be derived or does not need to be derived.

Constructors

InsufficientData

Insufficient information available to derive data.

Other Text

User provided reason for missingness

Instances

Instances details
Eq MissingReason Source # 
Instance details

Defined in Features.Compose

Show MissingReason Source # 
Instance details

Defined in Features.Compose

Generic MissingReason Source # 
Instance details

Defined in Features.Compose

Associated Types

type Rep MissingReason :: Type -> Type #

ToJSON MissingReason Source # 
Instance details

Defined in Features.Output

type Rep MissingReason Source # 
Instance details

Defined in Features.Compose

type Rep MissingReason = D1 ('MetaData "MissingReason" "Features.Compose" "hasklepias-0.17.0-inplace" 'False) (C1 ('MetaCons "InsufficientData" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Other" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data KnownSymbol name => Feature name d Source #

The Feature is an abstraction for named data, where the name is a *type*. Essentially, it is a container for FeatureData that assigns a name to the data.

Except when using pure to lift data into a Feature, Features can only be derived from other Feature via a Definition.

Instances

Instances details
Monad (Feature name) Source # 
Instance details

Defined in Features.Compose

Methods

(>>=) :: Feature name a -> (a -> Feature name b) -> Feature name b #

(>>) :: Feature name a -> Feature name b -> Feature name b #

return :: a -> Feature name a #

Functor (Feature name) Source # 
Instance details

Defined in Features.Compose

Methods

fmap :: (a -> b) -> Feature name a -> Feature name b #

(<$) :: a -> Feature name b -> Feature name a #

Applicative (Feature name) Source # 
Instance details

Defined in Features.Compose

Methods

pure :: a -> Feature name a #

(<*>) :: Feature name (a -> b) -> Feature name a -> Feature name b #

liftA2 :: (a -> b -> c) -> Feature name a -> Feature name b -> Feature name c #

(*>) :: Feature name a -> Feature name b -> Feature name b #

(<*) :: Feature name a -> Feature name b -> Feature name a #

Foldable (Feature name) Source # 
Instance details

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 #

sum :: Num a => Feature name a -> a #

product :: Num a => Feature name a -> a #

Traversable (Feature name) Source # 
Instance details

Defined in Features.Compose

Methods

traverse :: Applicative f => (a -> f b) -> Feature name a -> f (Feature name b) #

sequenceA :: Applicative f => Feature name (f a) -> f (Feature name a) #

mapM :: Monad m => (a -> m b) -> Feature name a -> m (Feature name b) #

sequence :: Monad m => Feature name (m a) -> m (Feature name a) #

Eq d => Eq (Feature name d) Source # 
Instance details

Defined in Features.Compose

Methods

(==) :: Feature name d -> Feature name d -> Bool #

(/=) :: Feature name d -> Feature name d -> Bool #

(KnownSymbol name, Show a) => Show (Feature name a) Source # 
Instance details

Defined in Features.Compose

Methods

showsPrec :: Int -> Feature name a -> ShowS #

show :: Feature name a -> String #

showList :: [Feature name a] -> ShowS #

(Typeable d, KnownSymbol n, ToJSON d, HasAttributes n d) => ToJSON (Feature n d) Source # 
Instance details

Defined in Features.Output

(KnownSymbol n, Show d, ToJSON d, Typeable d, HasAttributes n d) => ShapeOutput (Feature n d) Source # 
Instance details

Defined in Features.Output

DefineA (e -> d -> c -> b -> Feature n0 a) (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

defineA :: (e -> d -> c -> b -> Feature n0 a) -> Definition (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 # 
Instance details

Defined in Features.Compose

Methods

defineA :: (d -> c -> b -> Feature n0 a) -> Definition (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

DefineA (c -> b -> Feature n0 a) (Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

defineA :: (c -> b -> Feature n0 a) -> Definition (Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

DefineA (b -> Feature n0 a) (Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

defineA :: (b -> Feature n0 a) -> Definition (Feature n1 b -> Feature n0 a) Source #

Define (e -> d -> c -> b -> a) (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (e -> d -> c -> b -> a) -> Definition (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

Define (d -> c -> b -> a) (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (d -> c -> b -> a) -> Definition (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

Define (c -> b -> a) (Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (c -> b -> a) -> Definition (Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

Define (b -> a) (Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (b -> a) -> Definition (Feature n1 b -> Feature n0 a) Source #

Eval (Feature n2 c -> Feature n1 b -> Feature n0 a) (Feature n2 c, Feature n1 b) (Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

eval :: Definition (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 # 
Instance details

Defined in Features.Compose

Methods

eval :: Definition (Feature n1 b -> Feature n0 a) -> Feature n1 b -> Feature n0 a Source #

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 # 
Instance details

Defined in Features.Compose

Methods

eval :: Definition (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 # 
Instance details

Defined in Features.Compose

Methods

eval :: Definition (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 #

data FeatureN d Source #

The FeatureN type is similar to Feature where the name 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.

Instances

Instances details
Eq d => Eq (FeatureN d) Source # 
Instance details

Defined in Features.Compose

Methods

(==) :: FeatureN d -> FeatureN d -> Bool #

(/=) :: FeatureN d -> FeatureN d -> Bool #

Show d => Show (FeatureN d) Source # 
Instance details

Defined in Features.Compose

Methods

showsPrec :: Int -> FeatureN d -> ShowS #

show :: FeatureN d -> String #

showList :: [FeatureN d] -> ShowS #

featureDataL :: MissingReason -> FeatureData d Source #

Creates a missing FeatureData.

>>> featureDataL (Other "no good reason") :: FeatureData P.Int
MkFeatureData (Left (Other "no good reason"))
>>> featureDataL (Other "no good reason") :: FeatureData Text
MkFeatureData (Left (Other "no good reason"))

featureDataR :: d -> FeatureData d Source #

Creates a non-missing FeatureData. Since FeatureData is an instance of Applicative, pure is also a synonym of for featureDataR.

>>> featureDataR "aString"
MkFeatureData (Right "aString")
>>> featureDataR (1 :: P.Int)
MkFeatureData (Right 1)
>>> featureDataR ("aString", (1 :: P.Int))
MkFeatureData (Right ("aString",1))

makeFeature :: KnownSymbol name => FeatureData d -> Feature name d Source #

A utility for constructing a Feature from FeatureData. Since name 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) FeatureData content of a Feature.

getDataN :: FeatureN d -> FeatureData d Source #

Get the data of a FeatureN

getNameN :: FeatureN d -> Text Source #

Get the name of a FeatureN.

nameFeature :: forall name d. KnownSymbol name => Feature name d -> FeatureN d Source #

A utility for converting a Feature to FeatureN.

Feature Definitions

data Definition d where Source #

A Definition can be thought of as a lifted function. Specifically, the define function takes an arbitrary function (currently up to three arguments) and returns a Defintion 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 eval for evaluating Defintions.

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 Definitions via define (defineA). The define function takes a single function input and returns a lifted function. 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

The defineA function is similar, except that the return type of the input function is already lifted. In the example below, an input of Nothing 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

Instances details
Define (e -> d -> c -> b -> a) (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (e -> d -> c -> b -> a) -> Definition (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

Define (d -> c -> b -> a) (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (d -> c -> b -> a) -> Definition (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

Define (c -> b -> a) (Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (c -> b -> a) -> Definition (Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

Define (b -> a) (Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (b -> a) -> Definition (Feature n1 b -> Feature n0 a) Source #

Define (e -> d -> c -> b -> a) (FeatureData e -> FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (e -> d -> c -> b -> a) -> Definition (FeatureData e -> FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source #

Define (d -> c -> b -> a) (FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (d -> c -> b -> a) -> Definition (FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source #

Define (c -> b -> a) (FeatureData c -> FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (c -> b -> a) -> Definition (FeatureData c -> FeatureData b -> FeatureData a) Source #

Define (b -> a) (FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Methods

define :: (b -> a) -> Definition (FeatureData b -> FeatureData a) Source #

class DefineA inputs def | def -> inputs where Source #

See Define.

Methods

defineA :: inputs -> Definition def Source #

Instances

Instances details
DefineA (e -> d -> c -> b -> Feature n0 a) (Feature n4 e -> Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

defineA :: (e -> d -> c -> b -> Feature n0 a) -> Definition (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 # 
Instance details

Defined in Features.Compose

Methods

defineA :: (d -> c -> b -> Feature n0 a) -> Definition (Feature n3 d -> Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

DefineA (c -> b -> Feature n0 a) (Feature n2 c -> Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

defineA :: (c -> b -> Feature n0 a) -> Definition (Feature n2 c -> Feature n1 b -> Feature n0 a) Source #

DefineA (b -> Feature n0 a) (Feature n1 b -> Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

defineA :: (b -> Feature n0 a) -> Definition (Feature n1 b -> Feature n0 a) Source #

DefineA (e -> d -> c -> b -> FeatureData a) (FeatureData e -> FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Methods

defineA :: (e -> d -> c -> b -> FeatureData a) -> Definition (FeatureData e -> FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source #

DefineA (d -> c -> b -> FeatureData a) (FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Methods

defineA :: (d -> c -> b -> FeatureData a) -> Definition (FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) Source #

DefineA (c -> b -> FeatureData a) (FeatureData c -> FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

Methods

defineA :: (c -> b -> FeatureData a) -> Definition (FeatureData c -> FeatureData b -> FeatureData a) Source #

DefineA (b -> FeatureData a) (FeatureData b -> FeatureData a) Source # 
Instance details

Defined in Features.Compose

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

eval Source #

Arguments

:: Definition def

a Definition

-> args

a tuple of arguments to the Definition

-> return 

Instances

Instances details
Eval (FeatureData b -> FeatureData a) (FeatureData b) (FeatureData a) Source # 
Instance details

Defined in Features.Compose

Eval (FeatureData c -> FeatureData b -> FeatureData a) (FeatureData c, FeatureData b) (FeatureData a) Source # 
Instance details

Defined in Features.Compose

Eval (Feature n2 c -> Feature n1 b -> Feature n0 a) (Feature n2 c, Feature n1 b) (Feature n0 a) Source # 
Instance details

Defined in Features.Compose

Methods

eval :: Definition (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 # 
Instance details

Defined in Features.Compose

Methods

eval :: Definition (Feature n1 b -> Feature n0 a) -> Feature n1 b -> Feature n0 a Source #

Eval (FeatureData d -> FeatureData c -> FeatureData b -> FeatureData a) (FeatureData d, FeatureData c, FeatureData b) (FeatureData a) Source # 
Instance details

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 # 
Instance details

Defined in Features.Compose

Methods

eval :: Definition (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 # 
Instance details

Defined in Features.Compose

Methods

eval :: Definition (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 #

Adding Attributes to Features

data Attributes Source #

A data type for holding attritbutes of Features. This type and the HasAttributes are likely to change in future versions.

Instances

Instances details
Eq Attributes Source # 
Instance details

Defined in Features.Attributes

Show Attributes Source # 
Instance details

Defined in Features.Attributes

Generic Attributes Source # 
Instance details

Defined in Features.Attributes

Associated Types

type Rep Attributes :: Type -> Type #

ToJSON Attributes Source # 
Instance details

Defined in Features.Output

type Rep Attributes Source # 
Instance details

Defined in Features.Attributes

type Rep Attributes = D1 ('MetaData "Attributes" "Features.Attributes" "hasklepias-0.17.0-inplace" 'False) (C1 ('MetaCons "MkAttributes" 'PrefixI 'True) ((S1 ('MetaSel ('Just "getShortLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "getLongLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "getDerivation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "getPurpose") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Purpose))))

data Role Source #

A type to identify a feature's role in a research study.

Instances

Instances details
Eq Role Source # 
Instance details

Defined in Features.Attributes

Methods

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

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

Ord Role Source # 
Instance details

Defined in Features.Attributes

Methods

compare :: Role -> Role -> Ordering #

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

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

(>) :: Role -> Role -> Bool #

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

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

Show Role Source # 
Instance details

Defined in Features.Attributes

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

Generic Role Source # 
Instance details

Defined in Features.Attributes

Associated Types

type Rep Role :: Type -> Type #

Methods

from :: Role -> Rep Role x #

to :: Rep Role x -> Role #

ToJSON Role Source # 
Instance details

Defined in Features.Output

type Rep Role Source # 
Instance details

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))))

data Purpose Source #

A type to identify a feature's purpose

Constructors

MkPurpose 

Fields

Instances

Instances details
Eq Purpose Source # 
Instance details

Defined in Features.Attributes

Methods

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

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

Show Purpose Source # 
Instance details

Defined in Features.Attributes

Generic Purpose Source # 
Instance details

Defined in Features.Attributes

Associated Types

type Rep Purpose :: Type -> Type #

Methods

from :: Purpose -> Rep Purpose x #

to :: Rep Purpose x -> Purpose #

ToJSON Purpose Source # 
Instance details

Defined in Features.Output

type Rep Purpose Source # 
Instance details

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.

basicAttributes Source #

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 

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

Instances details
Show Featureset Source # 
Instance details

Defined in Features.Featureset

ToJSON Featureset Source # 
Instance details

Defined in Features.Featureset

ShapeCohort Featureset Source # 
Instance details

Defined in Cohort.Output

newtype FeaturesetList Source #

A newtype wrapper for a NonEmpty Featureset.

Instances

Instances details
Show FeaturesetList Source # 
Instance details

Defined in Features.Featureset

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.

data OutputShape d Source #

A type used to determine the output shape of a Feature.

Instances

Instances details
Show (OutputShape a) Source # 
Instance details

Defined in Features.Output

ToJSON (OutputShape a) Source # 
Instance details

Defined in Features.Output

Feature definition builders

A collection of pre-defined functions which build common feature definitions used in epidemiologic cohorts.

buildIsEnrolled Source #

Arguments

:: (Intervallic i0 a, Monoid (container (Interval a)), Applicative container, Witherable container) 
=> Predicate (Event a)

The predicate to filter to Enrollment events (e.g. isEnrollment)

-> 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. isEnrollment)

-> 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

buildNofX Source #

Arguments

:: (Intervallic i a, Witherable container) 
=> (Bool -> outputType)

casting function

-> Natural

minimum number of cases

-> (Index i a -> AssessmentInterval a)

function to transform a Index to an AssessmentInterval

-> 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?

buildNofXBool Source #

Arguments

:: (Intervallic i a, Witherable container) 
=> Natural

minimum number of cases

-> (Index i a -> AssessmentInterval a)

function to transform a Index to an AssessmentInterval

-> 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) 

buildNofX specialized to return 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 #

buildNofX specialized to return Binary.

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 makeBaselineFromIndex)

-> 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 makeBaselineFromIndex)

-> [Text]

list of Concepts passed to containsConcepts

-> 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.

buildNofXWithGap Source #

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?

buildNofXWithGapBool 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 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.

buildNofUniqueBegins Source #

Arguments

:: (Intervallic i a, IntervalSizeable a b, Witherable container) 
=> (Index i a -> AssessmentInterval a)

function to transform a Index to an AssessmentInterval

-> 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?

atleastNofX Source #

Arguments

:: Int

n

-> [Text]

x

-> Events a 
-> Bool 

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

nthConceptOccurrence Source #

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 Maybe Event, based on a provided function, with the provided concepts. For example, see firstConceptOccurrence and lastConceptOccurrence.

firstConceptOccurrence :: Witherable f => [Text] -> f (Event a) -> Maybe (Event a) Source #

Finds the *first* occurrence of an Event with at least one of the concepts. Assumes the input Events list is appropriately sorted.

Reshaping containers

allPairs :: Applicative f => f a -> f b -> f (a, b) Source #

Generate all pair-wise combinations from two lists.

pairs :: [a] -> [(a, a)] Source #

Generate all pair-wise combinations of a single list.

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

makeConceptsFilter Source #

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

yearFromDay :: Day -> Year Source #

Gets the Year from a Day.

Functions for manipulating intervals

lookback Source #

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)

lookahead Source #

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 F n a = Feature n a Source #

Type synonym for Feature.

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

Instances details
(Eq what, Eq when) => Eq (Occurrence what when) Source # 
Instance details

Defined in Hasklepias.Misc

Methods

(==) :: Occurrence what when -> Occurrence what when -> Bool #

(/=) :: Occurrence what when -> Occurrence what when -> Bool #

(OccurrenceReason r, Ord b) => Ord (Occurrence r b) Source # 
Instance details

Defined in Hasklepias.Misc

Methods

compare :: Occurrence r b -> Occurrence r b -> Ordering #

(<) :: Occurrence r b -> Occurrence r b -> Bool #

(<=) :: Occurrence r b -> Occurrence r b -> Bool #

(>) :: Occurrence r b -> Occurrence r b -> Bool #

(>=) :: Occurrence r b -> Occurrence r b -> Bool #

max :: Occurrence r b -> Occurrence r b -> Occurrence r b #

min :: Occurrence r b -> Occurrence r b -> Occurrence r b #

(Show what, Show when) => Show (Occurrence what when) Source # 
Instance details

Defined in Hasklepias.Misc

Methods

showsPrec :: Int -> Occurrence what when -> ShowS #

show :: Occurrence what when -> String #

showList :: [Occurrence what when] -> ShowS #

Generic (Occurrence what when) Source # 
Instance details

Defined in Hasklepias.Misc

Associated Types

type Rep (Occurrence what when) :: Type -> Type #

Methods

from :: Occurrence what when -> Rep (Occurrence what when) x #

to :: Rep (Occurrence what when) x -> Occurrence what when #

type Rep (Occurrence what when) Source # 
Instance details

Defined in Hasklepias.Misc

type Rep (Occurrence what when) = D1 ('MetaData "Occurrence" "Hasklepias.Misc" "hasklepias-0.17.0-inplace" 'True) (C1 ('MetaCons "MkOccurrence" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (what, EventTime when))))

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

Instances details
(Eq cr, Eq or) => Eq (CensoringReason cr or) Source # 
Instance details

Defined in Hasklepias.Misc

Methods

(==) :: CensoringReason cr or -> CensoringReason cr or -> Bool #

(/=) :: CensoringReason cr or -> CensoringReason cr or -> Bool #

(Show cr, Show or) => Show (CensoringReason cr or) Source # 
Instance details

Defined in Hasklepias.Misc

Generic (CensoringReason cr or) Source # 
Instance details

Defined in Hasklepias.Misc

Associated Types

type Rep (CensoringReason cr or) :: Type -> Type #

Methods

from :: CensoringReason cr or -> Rep (CensoringReason cr or) x #

to :: Rep (CensoringReason cr or) x -> CensoringReason cr or #

type Rep (CensoringReason cr or) Source # 
Instance details

Defined in Hasklepias.Misc

type Rep (CensoringReason cr or) = D1 ('MetaData "CensoringReason" "Hasklepias.Misc" "hasklepias-0.17.0-inplace" 'False) (C1 ('MetaCons "AdminCensor" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "C" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 cr)) :+: C1 ('MetaCons "O" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 or))))

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

Instances details
(Eq censors, Eq outcomes, Eq b) => Eq (CensoredOccurrence censors outcomes b) Source # 
Instance details

Defined in Hasklepias.Misc

Methods

(==) :: CensoredOccurrence censors outcomes b -> CensoredOccurrence censors outcomes b -> Bool #

(/=) :: CensoredOccurrence censors outcomes b -> CensoredOccurrence censors outcomes b -> Bool #

(OccurrenceReason c, OccurrenceReason o, Show b) => Show (CensoredOccurrence c o b) Source # 
Instance details

Defined in Hasklepias.Misc

Generic (CensoredOccurrence censors outcomes b) Source # 
Instance details

Defined in Hasklepias.Misc

Associated Types

type Rep (CensoredOccurrence censors outcomes b) :: Type -> Type #

Methods

from :: CensoredOccurrence censors outcomes b -> Rep (CensoredOccurrence censors outcomes b) x #

to :: Rep (CensoredOccurrence censors outcomes b) x -> CensoredOccurrence censors outcomes b #

type Rep (CensoredOccurrence censors outcomes b) Source # 
Instance details

Defined in Hasklepias.Misc

type Rep (CensoredOccurrence censors outcomes b) = D1 ('MetaData "CensoredOccurrence" "Hasklepias.Misc" "hasklepias-0.17.0-inplace" 'False) (C1 ('MetaCons "MkCensoredOccurrence" 'PrefixI 'True) (S1 ('MetaSel ('Just "reason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CensoringReason censors outcomes)) :*: S1 ('MetaSel ('Just "time") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MaybeCensored (EventTime b)))))

adminCensor :: EventTime b -> CensoredOccurrence c o b Source #

Creates an administratively censored occurrence.

Specifying and building cohorts

Defining Cohorts

newtype Subject d Source #

A subject is just a pair of ID and data.

Constructors

MkSubject (ID, d) 

Instances

Instances details
Functor Subject Source # 
Instance details

Defined in Cohort.Core

Methods

fmap :: (a -> b) -> Subject a -> Subject b #

(<$) :: a -> Subject b -> Subject a #

Eq d => Eq (Subject d) Source # 
Instance details

Defined in Cohort.Core

Methods

(==) :: Subject d -> Subject d -> Bool #

(/=) :: Subject d -> Subject d -> Bool #

Show d => Show (Subject d) Source # 
Instance details

Defined in Cohort.Core

Methods

showsPrec :: Int -> Subject d -> ShowS #

show :: Subject d -> String #

showList :: [Subject d] -> ShowS #

Generic (Subject d) Source # 
Instance details

Defined in Cohort.Core

Associated Types

type Rep (Subject d) :: Type -> Type #

Methods

from :: Subject d -> Rep (Subject d) x #

to :: Rep (Subject d) x -> Subject d #

FromJSON d => FromJSON (Subject d) Source # 
Instance details

Defined in Cohort.Core

type Rep (Subject d) Source # 
Instance details

Defined in Cohort.Core

type Rep (Subject d) = D1 ('MetaData "Subject" "Cohort.Core" "hasklepias-0.17.0-inplace" 'True) (C1 ('MetaCons "MkSubject" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ID, d))))

type ID = Text Source #

A subject identifier. Currently, simply Text.

newtype Population d Source #

A population is a list of Subjects

Constructors

MkPopulation [Subject d] 

Instances

Instances details
Functor Population Source # 
Instance details

Defined in Cohort.Core

Methods

fmap :: (a -> b) -> Population a -> Population b #

(<$) :: a -> Population b -> Population a #

Eq d => Eq (Population d) Source # 
Instance details

Defined in Cohort.Core

Methods

(==) :: Population d -> Population d -> Bool #

(/=) :: Population d -> Population d -> Bool #

Show d => Show (Population d) Source # 
Instance details

Defined in Cohort.Core

Generic (Population d) Source # 
Instance details

Defined in Cohort.Core

Associated Types

type Rep (Population d) :: Type -> Type #

Methods

from :: Population d -> Rep (Population d) x #

to :: Rep (Population d) x -> Population d #

FromJSON d => FromJSON (Population d) Source # 
Instance details

Defined in Cohort.Core

type Rep (Population d) Source # 
Instance details

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])))

data ObsUnit d Source #

An observational unit is what a subject may be transformed into.

Constructors

MkObsUnit 

Fields

Instances

Instances details
Eq d => Eq (ObsUnit d) Source # 
Instance details

Defined in Cohort.Core

Methods

(==) :: ObsUnit d -> ObsUnit d -> Bool #

(/=) :: ObsUnit d -> ObsUnit d -> Bool #

Show d => Show (ObsUnit d) Source # 
Instance details

Defined in Cohort.Core

Methods

showsPrec :: Int -> ObsUnit d -> ShowS #

show :: ObsUnit d -> String #

showList :: [ObsUnit d] -> ShowS #

Generic (ObsUnit d) Source # 
Instance details

Defined in Cohort.Core

Associated Types

type Rep (ObsUnit d) :: Type -> Type #

Methods

from :: ObsUnit d -> Rep (ObsUnit d) x #

to :: Rep (ObsUnit d) x -> ObsUnit d #

ToJSON d => ToJSON (ObsUnit d) Source # 
Instance details

Defined in Cohort.Output

type Rep (ObsUnit d) Source # 
Instance details

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

Instances details
Eq d => Eq (CohortData d) Source # 
Instance details

Defined in Cohort.Core

Methods

(==) :: CohortData d -> CohortData d -> Bool #

(/=) :: CohortData d -> CohortData d -> Bool #

Show d => Show (CohortData d) Source # 
Instance details

Defined in Cohort.Core

Generic (CohortData d) Source # 
Instance details

Defined in Cohort.Core

Associated Types

type Rep (CohortData d) :: Type -> Type #

Methods

from :: CohortData d -> Rep (CohortData d) x #

to :: Rep (CohortData d) x -> CohortData d #

ToJSON d => ToJSON (CohortData d) Source # 
Instance details

Defined in Cohort.Output

type Rep (CohortData d) Source # 
Instance details

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])))

newtype Cohort d Source #

A cohort is a list of observational units along with AttritionInfo regarding the number of subjects excluded by the Criteria.

Instances

Instances details
Eq d => Eq (Cohort d) Source # 
Instance details

Defined in Cohort.Core

Methods

(==) :: Cohort d -> Cohort d -> Bool #

(/=) :: Cohort d -> Cohort d -> Bool #

Show d => Show (Cohort d) Source # 
Instance details

Defined in Cohort.Core

Methods

showsPrec :: Int -> Cohort d -> ShowS #

show :: Cohort d -> String #

showList :: [Cohort d] -> ShowS #

Generic (Cohort d) Source # 
Instance details

Defined in Cohort.Core

Associated Types

type Rep (Cohort d) :: Type -> Type #

Methods

from :: Cohort d -> Rep (Cohort d) x #

to :: Rep (Cohort d) x -> Cohort d #

ToJSON d => ToJSON (Cohort d) Source # 
Instance details

Defined in Cohort.Output

type Rep (Cohort d) Source # 
Instance details

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 Criteria and another that transforms a subject's input data into the desired return type.

newtype AttritionInfo Source #

A type which collects the counts of subjects included or excluded.

Instances

Instances details
Eq AttritionInfo Source # 
Instance details

Defined in Cohort.Core

Show AttritionInfo Source # 
Instance details

Defined in Cohort.Core

Generic AttritionInfo Source # 
Instance details

Defined in Cohort.Core

Associated Types

type Rep AttritionInfo :: Type -> Type #

ToJSON AttritionInfo Source # 
Instance details

Defined in Cohort.Output

type Rep AttritionInfo Source # 
Instance details

Defined in Cohort.Core

type Rep AttritionInfo = D1 ('MetaData "AttritionInfo" "Cohort.Core" "hasklepias-0.17.0-inplace" 'True) (C1 ('MetaCons "MkAttritionInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (CohortStatus, Natural)))))

specifyCohort :: (d1 -> Criteria) -> (d1 -> d0) -> CohortSpec d1 d0 Source #

Creates a CohortSpec.

makeObsUnitFeatures :: (d1 -> d0) -> Subject d1 -> ObsUnit d0 Source #

Tranforms a Subject into a ObsUnit.

evalCohort :: CohortSpec d1 d0 -> Population d1 -> Cohort d0 Source #

Evaluates a CohortSpec on a 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.

data Index i a Source #

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

Instances details
Functor i => Functor (Index i) Source # 
Instance details

Defined in Cohort.Index

Methods

fmap :: (a -> b) -> Index i a -> Index i b #

(<$) :: a -> Index i b -> Index i a #

Intervallic i a => Intervallic (Index i) a Source # 
Instance details

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 # 
Instance details

Defined in Cohort.Index

Methods

(==) :: Index i a -> Index i a -> Bool #

(/=) :: Index i a -> Index i a -> Bool #

Show (i a) => Show (Index i a) Source # 
Instance details

Defined in Cohort.Index

Methods

showsPrec :: Int -> Index i a -> ShowS #

show :: Index i a -> String #

showList :: [Index i a] -> ShowS #

Generic (Index i a) Source # 
Instance details

Defined in Cohort.Index

Associated Types

type Rep (Index i a) :: Type -> Type #

Methods

from :: Index i a -> Rep (Index i a) x #

to :: Rep (Index i a) x -> Index i a #

(Intervallic i a, ToJSON (i a)) => ToJSON (Index i a) Source # 
Instance details

Defined in Cohort.Index

Methods

toJSON :: Index i a -> Value #

toEncoding :: Index i a -> Encoding #

toJSONList :: [Index i a] -> Value #

toEncodingList :: [Index i a] -> Encoding #

type Rep (Index i a) Source # 
Instance details

Defined in Cohort.Index

type Rep (Index i a) = D1 ('MetaData "Index" "Cohort.Index" "hasklepias-0.17.0-inplace" 'True) (C1 ('MetaCons "MkIndex" 'PrefixI 'True) (S1 ('MetaSel ('Just "getIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (i a))))

makeIndex :: Intervallic i a => i a -> Index i a Source #

Creates a new Index.

Assessment Intervals

The assessment intervals provided are:

  • Baseline: an interval which either meets or precedes index. 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 is startedBy, metBy, or after an Index. Outcomes are typically assessed during followup intervals. Similar to Baseline, 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

Instances details
Functor BaselineInterval Source # 
Instance details

Defined in Cohort.AssessmentIntervals

Methods

fmap :: (a -> b) -> BaselineInterval a -> BaselineInterval b #

(<$) :: a -> BaselineInterval b -> BaselineInterval a #

Ord a => Intervallic BaselineInterval a Source # 
Instance details

Defined in Cohort.AssessmentIntervals

Eq a => Eq (BaselineInterval a) Source # 
Instance details

Defined in Cohort.AssessmentIntervals

(Show a, Ord a) => Show (BaselineInterval a) Source # 
Instance details

Defined in Cohort.AssessmentIntervals

Generic (BaselineInterval a) Source # 
Instance details

Defined in Cohort.AssessmentIntervals

Associated Types

type Rep (BaselineInterval a) :: Type -> Type #

type Rep (BaselineInterval a) Source # 
Instance details

Defined in Cohort.AssessmentIntervals

type Rep (BaselineInterval a) = D1 ('MetaData "BaselineInterval" "Cohort.AssessmentIntervals" "hasklepias-0.17.0-inplace" 'True) (C1 ('MetaCons "MkBaselineInterval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Interval a))))

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 (baseline d i) i = Meets

The baselineBefore function should satisfy:

Before
relate (baselineBefore s d i) i = Before
>>> import Cohort.Index
>>> import IntervalAlgebra
>>> x = makeIndex (beginerval 1 10)
>>> b =baseline 10 x
>>> b
>>> relate b x
MkBaselineInterval (0, 10)
Meets
>>> import Cohort.Index
>>> import IntervalAlgebra
>>> x = makeIndex (beginerval 1 10)
>>> b = baselineBefore 2 4 x
>>> b
>>> relate b x
MkBaselineInterval (4, 8)
Before

Minimal complete definition

Nothing

Methods

baseline Source #

Arguments

:: IntervalSizeable a b 
=> b

duration of baseline

-> Index i a

the Index event

-> BaselineInterval a 

Creates a BaselineInterval of the given duration that Meets the Index interval.

baselineBefore Source #

Arguments

:: IntervalSizeable a b 
=> b

duration to shift back

-> b

duration of baseline

-> Index i a

the Index event

-> BaselineInterval a 

Creates a BaselineInterval of the given duration that precedes the Index interval.

Instances

Instances details
Ord a => Baseline Interval a Source # 
Instance details

Defined in Cohort.AssessmentIntervals

data FollowupInterval a Source #

A type to contain followup intervals. See the Followup typeclass for methods to create values of this type.

Instances

Instances details
Functor FollowupInterval Source # 
Instance details

Defined in Cohort.AssessmentIntervals

Methods

fmap :: (a -> b) -> FollowupInterval a -> FollowupInterval b #

(<$) :: a -> FollowupInterval b -> FollowupInterval a #

Ord a => Intervallic FollowupInterval a Source # 
Instance details

Defined in Cohort.AssessmentIntervals

Eq a => Eq (FollowupInterval a) Source # 
Instance details

Defined in Cohort.AssessmentIntervals

(Show a, Ord a) => Show (FollowupInterval a) Source # 
Instance details

Defined in Cohort.AssessmentIntervals

Generic (FollowupInterval a) Source # 
Instance details

Defined in Cohort.AssessmentIntervals

Associated Types

type Rep (FollowupInterval a) :: Type -> Type #

type Rep (FollowupInterval a) Source # 
Instance details

Defined in Cohort.AssessmentIntervals

type Rep (FollowupInterval a) = D1 ('MetaData "FollowupInterval" "Cohort.AssessmentIntervals" "hasklepias-0.17.0-inplace" 'True) (C1 ('MetaCons "MkFollowupInterval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Interval a))))

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 (followup d i) i = StartedBy

The followupMetBy function should satisfy:

MetBy
relate (followupMetBy d i) i = MetBy

The followupAfter function should satisfy:

After
relate (followupAfter s d i) i = After
>>> import Cohort.Index
>>> import IntervalAlgebra
>>> x = makeIndex (beginerval 1 10)
>>> f = followup 10 x
>>> f
>>> relate f x
MkFollowupInterval (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 x
MkFollowupInterval (10, 12)
StartedBy
>>> import Cohort.Index
>>> import IntervalAlgebra
>>> x = makeIndex (beginerval 1 10)
>>> f = followupMetBy 9 x
>>> f
>>> relate f x
MkFollowupInterval (11, 20)
MetBy
>>> import Cohort.Index
>>> import IntervalAlgebra
>>> x = makeIndex (beginerval 1 10)
>>> f = followupAfter 1 9 x
>>> f
>>> relate f x
MkFollowupInterval (12, 21)
After

Minimal complete definition

Nothing

Methods

followup Source #

Arguments

:: (IntervalSizeable a b, Intervallic i a) 
=> b

duration of followup

-> Index i a

the Index event

-> FollowupInterval a 

followupMetBy Source #

Arguments

:: (IntervalSizeable a b, Intervallic i a) 
=> b

duration of followup

-> Index i a

the Index event

-> FollowupInterval a 

followupAfter Source #

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 Index event

-> FollowupInterval a 

data AssessmentInterval a Source #

A data type that contains variants of intervals during which assessment may occur.

Instances

Instances details
Functor AssessmentInterval Source # 
Instance details

Defined in Cohort.AssessmentIntervals

Ord a => Intervallic AssessmentInterval a Source # 
Instance details

Defined in Cohort.AssessmentIntervals

Eq a => Eq (AssessmentInterval a) Source # 
Instance details

Defined in Cohort.AssessmentIntervals

(Show a, Ord a) => Show (AssessmentInterval a) Source # 
Instance details

Defined in Cohort.AssessmentIntervals

Generic (AssessmentInterval a) Source # 
Instance details

Defined in Cohort.AssessmentIntervals

Associated Types

type Rep (AssessmentInterval a) :: Type -> Type #

type Rep (AssessmentInterval a) Source # 
Instance details

Defined in Cohort.AssessmentIntervals

type Rep (AssessmentInterval a) = D1 ('MetaData "AssessmentInterval" "Cohort.AssessmentIntervals" "hasklepias-0.17.0-inplace" 'False) (C1 ('MetaCons "Bl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BaselineInterval a))) :+: C1 ('MetaCons "Fl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (FollowupInterval a))))

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 x
Bl (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 x
Bl (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 x
Fl (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 x
Fl (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 x
Fl (MkFollowupInterval (21, 31))

Criteria

data Criterion Source #

A type that is simply a 'FeatureN Status', that is, a feature that identifies whether to Include or Exclude a subject.

Instances

Instances details
Eq Criterion Source # 
Instance details

Defined in Cohort.Criteria

Show Criterion Source # 
Instance details

Defined in Cohort.Criteria

newtype Criteria Source #

A nonempty collection of Criterion paired with a Natural number.

Constructors

MkCriteria 

Instances

Instances details
Eq Criteria Source # 
Instance details

Defined in Cohort.Criteria

Show Criteria Source # 
Instance details

Defined in Cohort.Criteria

data Status Source #

Defines the return type for Criterion indicating whether to include or exclude a subject.

Constructors

Include 
Exclude 

Instances

Instances details
Eq Status Source # 
Instance details

Defined in Cohort.Criteria

Methods

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

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

Show Status Source # 
Instance details

Defined in Cohort.Criteria

data CohortStatus Source #

Defines subject's diposition in a cohort either included or which criterion they were excluded by. See checkCohortStatus for evaluating a Criteria to determine CohortStatus.

Constructors

Included 
ExcludedBy (Natural, Text) 

Instances

Instances details
Eq CohortStatus Source # 
Instance details

Defined in Cohort.Criteria

Ord CohortStatus Source # 
Instance details

Defined in Cohort.Criteria

Show CohortStatus Source # 
Instance details

Defined in Cohort.Criteria

Generic CohortStatus Source # 
Instance details

Defined in Cohort.Criteria

Associated Types

type Rep CohortStatus :: Type -> Type #

ToJSON CohortStatus Source # 
Instance details

Defined in Cohort.Output

type Rep CohortStatus Source # 
Instance details

Defined in Cohort.Criteria

type Rep CohortStatus = D1 ('MetaData "CohortStatus" "Cohort.Criteria" "hasklepias-0.17.0-inplace" 'False) (C1 ('MetaCons "Included" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExcludedBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Natural, Text))))

criteria :: NonEmpty Criterion -> Criteria Source #

Constructs a Criteria from a NonEmpty collection of Criterion.

excludeIf :: Bool -> Status Source #

Helper to convert a Bool to a Status

>>> excludeIf True
>>> excludeIf False
Exclude
Include

includeIf :: Bool -> Status Source #

Helper to convert a Bool to a Status

>>> includeIf True
>>> includeIf False
Include
Exclude

initStatusInfo :: Criteria -> NonEmpty CohortStatus Source #

Initializes a container of CohortStatus from a Criteria. This can be used to collect generate all the possible Exclusion/Inclusion reasons.

checkCohortStatus :: Criteria -> CohortStatus Source #

Converts a subject's Criteria to a CohortStatus. The status is set to Included if none of the Criterion have a status of 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

Instances details
Eq ParseError Source # 
Instance details

Defined in Cohort.Input

Show ParseError Source # 
Instance details

Defined in Cohort.Input

Output

data CohortShape d Source #

A type used to determine the output shape of a Cohort.

Instances

Instances details
Show d => Show (CohortShape d) Source # 
Instance details

Defined in Cohort.Output

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

Instances details
ShapeCohort Featureset Source # 
Instance details

Defined in Cohort.Output

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

makeCohortApp Source #

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

Rexported Functions and modules