{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE Safe #-}
module Hasklepias.Functions(
isNotEmpty
, atleastNofX
, twoXOrOneY
, nthConceptOccurrence
, firstConceptOccurrence
, allPairs
, splitByConcepts
, makeConceptsFilter
, makePairedFilter
) where
import Data.Text ( Text )
import Control.Applicative ( Applicative(liftA2) )
import IntervalAlgebra ( Intervallic(..)
, ComparativePredicateOf1
, ComparativePredicateOf2
, Interval )
import IntervalAlgebra.PairedInterval ( PairedInterval, getPairData )
import Hasklepias.Types.Event ( Events
, Event
, ConceptEvent
, ctxt )
import Hasklepias.Types.Context ( Concept
, Concepts
, Context
, HasConcept( hasConcepts ) )
import Safe ( headMay, lastMay )
import safe Data.Bool ( Bool, (&&), not, (||) )
import safe Data.Function ( (.), ($) )
import safe Data.Int ( Int )
import safe Data.List ( filter, length, null )
import safe Data.Maybe ( Maybe(..) )
import safe Data.Ord ( Ord((>=)) )
isNotEmpty :: [a] -> Bool
isNotEmpty :: [a] -> Bool
isNotEmpty = Bool -> Bool
not(Bool -> Bool) -> ([a] -> Bool) -> [a] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null
makeConceptsFilter ::
[Text]
-> Events a
-> Events a
makeConceptsFilter :: [Text] -> Events a -> Events a
makeConceptsFilter [Text]
cpts = (Event a -> Bool) -> Events a -> Events a
forall a. (a -> Bool) -> [a] -> [a]
filter (Event a -> [Text] -> Bool
forall a. HasConcept a => a -> [Text] -> Bool
`hasConcepts` [Text]
cpts)
nthConceptOccurrence ::
(Events a -> Maybe (Event a))
-> [Text]
-> Events a
-> Maybe (Event a)
nthConceptOccurrence :: (Events a -> Maybe (Event a))
-> [Text] -> Events a -> Maybe (Event a)
nthConceptOccurrence Events a -> Maybe (Event a)
f [Text]
c = Events a -> Maybe (Event a)
f(Events a -> Maybe (Event a))
-> (Events a -> Events a) -> Events a -> Maybe (Event a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[Text] -> Events a -> Events a
forall a. [Text] -> Events a -> Events a
makeConceptsFilter [Text]
c
firstConceptOccurrence ::
[Text]
-> Events a
-> Maybe (Event a)
firstConceptOccurrence :: [Text] -> Events a -> Maybe (Event a)
firstConceptOccurrence = (Events a -> Maybe (Event a))
-> [Text] -> Events a -> Maybe (Event a)
forall a.
(Events a -> Maybe (Event a))
-> [Text] -> Events a -> Maybe (Event a)
nthConceptOccurrence Events a -> Maybe (Event a)
forall a. [a] -> Maybe a
headMay
lastConceptOccurrence ::
[Text]
-> Events a
-> Maybe (Event a)
lastConceptOccurrence :: [Text] -> Events a -> Maybe (Event a)
lastConceptOccurrence = (Events a -> Maybe (Event a))
-> [Text] -> Events a -> Maybe (Event a)
forall a.
(Events a -> Maybe (Event a))
-> [Text] -> Events a -> Maybe (Event a)
nthConceptOccurrence Events a -> Maybe (Event a)
forall a. [a] -> Maybe a
lastMay
atleastNofX ::
Int
-> [Text]
-> Events a -> Bool
atleastNofX :: Int -> [Text] -> Events a -> Bool
atleastNofX Int
n [Text]
x Events a
es = Events a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Text] -> Events a -> Events a
forall a. [Text] -> Events a -> Events a
makeConceptsFilter [Text]
x Events a
es) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n
twoXOrOneY :: [Text] -> [Text] -> Events a -> Bool
twoXOrOneY :: [Text] -> [Text] -> Events a -> Bool
twoXOrOneY [Text]
x [Text]
y Events a
es = Int -> [Text] -> Events a -> Bool
forall a. Int -> [Text] -> Events a -> Bool
atleastNofX Int
2 [Text]
x Events a
es Bool -> Bool -> Bool
||
Int -> [Text] -> Events a -> Bool
forall a. Int -> [Text] -> Events a -> Bool
atleastNofX Int
1 [Text]
y Events a
es
makePairPredicate :: Ord a =>
ComparativePredicateOf2 (i0 a) ((PairedInterval b) a)
-> i0 a
-> (b -> Bool)
-> (PairedInterval b a -> Bool)
makePairPredicate :: ComparativePredicateOf2 (i0 a) (PairedInterval b a)
-> i0 a -> (b -> Bool) -> PairedInterval b a -> Bool
makePairPredicate ComparativePredicateOf2 (i0 a) (PairedInterval b a)
pi i0 a
i b -> Bool
pd PairedInterval b a
x = ComparativePredicateOf2 (i0 a) (PairedInterval b a)
pi i0 a
i PairedInterval b a
x Bool -> Bool -> Bool
&& b -> Bool
pd (PairedInterval b a -> b
forall b a. PairedInterval b a -> b
getPairData PairedInterval b a
x)
makePairedFilter :: Ord a =>
ComparativePredicateOf2 (i0 a) ((PairedInterval b) a)
-> i0 a
-> (b -> Bool)
-> [PairedInterval b a]
-> [PairedInterval b a]
makePairedFilter :: ComparativePredicateOf2 (i0 a) (PairedInterval b a)
-> i0 a
-> (b -> Bool)
-> [PairedInterval b a]
-> [PairedInterval b a]
makePairedFilter ComparativePredicateOf2 (i0 a) (PairedInterval b a)
fi i0 a
i b -> Bool
fc = (PairedInterval b a -> Bool)
-> [PairedInterval b a] -> [PairedInterval b a]
forall a. (a -> Bool) -> [a] -> [a]
filter (ComparativePredicateOf2 (i0 a) (PairedInterval b a)
-> i0 a -> (b -> Bool) -> PairedInterval b a -> Bool
forall a (i0 :: * -> *) b.
Ord a =>
ComparativePredicateOf2 (i0 a) (PairedInterval b a)
-> i0 a -> (b -> Bool) -> PairedInterval b a -> Bool
makePairPredicate ComparativePredicateOf2 (i0 a) (PairedInterval b a)
fi i0 a
i b -> Bool
fc)
allPairs :: [a] -> [b] -> [(a, b)]
allPairs :: [a] -> [b] -> [(a, b)]
allPairs = (a -> b -> (a, b)) -> [a] -> [b] -> [(a, b)]
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,)
splitByConcepts :: [Text]
-> [Text]
-> Events a
-> (Events a, Events a)
splitByConcepts :: [Text] -> [Text] -> Events a -> (Events a, Events a)
splitByConcepts [Text]
c1 [Text]
c2 Events a
es = ( (Event a -> Bool) -> Events a -> Events a
forall a. (a -> Bool) -> [a] -> [a]
filter (Event a -> [Text] -> Bool
forall a. HasConcept a => a -> [Text] -> Bool
`hasConcepts` [Text]
c1) Events a
es
, (Event a -> Bool) -> Events a -> Events a
forall a. (a -> Bool) -> [a] -> [a]
filter (Event a -> [Text] -> Bool
forall a. HasConcept a => a -> [Text] -> Bool
`hasConcepts` [Text]
c2) Events a
es)