{-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DeriveGeneric #-}
module Hasklepias.Misc (
F
, Def
, Occurrence(..)
, makeOccurrence
, getOccurrenceReason
, getOccurrenceTime
, CensoringReason(..)
, OccurrenceReason(..)
, CensoredOccurrence(..)
, adminCensor
) where
import Features.Compose ( Feature, Definition )
import Data.Bool ( otherwise, (&&) )
import Data.Eq ( Eq(..) )
import Data.Ord ( Ord(..), Ordering(..) )
import Data.Semigroup ( Semigroup((<>)) )
import GHC.Generics ( Generic )
import GHC.Show ( Show(..) )
import Stype.Numeric.Censored ( MaybeCensored(..) )
import Stype.Numeric.Continuous ( EventTime )
type F n a = Feature n a
type Def d = Definition d
class (Ord a, Show a) => OccurrenceReason a where
newtype Occurrence what when = MkOccurrence ( what , EventTime when )
deriving (Occurrence what when -> Occurrence what when -> Bool
(Occurrence what when -> Occurrence what when -> Bool)
-> (Occurrence what when -> Occurrence what when -> Bool)
-> Eq (Occurrence what when)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall what when.
(Eq what, Eq when) =>
Occurrence what when -> Occurrence what when -> Bool
/= :: Occurrence what when -> Occurrence what when -> Bool
$c/= :: forall what when.
(Eq what, Eq when) =>
Occurrence what when -> Occurrence what when -> Bool
== :: Occurrence what when -> Occurrence what when -> Bool
$c== :: forall what when.
(Eq what, Eq when) =>
Occurrence what when -> Occurrence what when -> Bool
Eq, Int -> Occurrence what when -> ShowS
[Occurrence what when] -> ShowS
Occurrence what when -> String
(Int -> Occurrence what when -> ShowS)
-> (Occurrence what when -> String)
-> ([Occurrence what when] -> ShowS)
-> Show (Occurrence what when)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall what when.
(Show what, Show when) =>
Int -> Occurrence what when -> ShowS
forall what when.
(Show what, Show when) =>
[Occurrence what when] -> ShowS
forall what when.
(Show what, Show when) =>
Occurrence what when -> String
showList :: [Occurrence what when] -> ShowS
$cshowList :: forall what when.
(Show what, Show when) =>
[Occurrence what when] -> ShowS
show :: Occurrence what when -> String
$cshow :: forall what when.
(Show what, Show when) =>
Occurrence what when -> String
showsPrec :: Int -> Occurrence what when -> ShowS
$cshowsPrec :: forall what when.
(Show what, Show when) =>
Int -> Occurrence what when -> ShowS
Show, (forall x. Occurrence what when -> Rep (Occurrence what when) x)
-> (forall x. Rep (Occurrence what when) x -> Occurrence what when)
-> Generic (Occurrence what when)
forall x. Rep (Occurrence what when) x -> Occurrence what when
forall x. Occurrence what when -> Rep (Occurrence what when) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall what when x.
Rep (Occurrence what when) x -> Occurrence what when
forall what when x.
Occurrence what when -> Rep (Occurrence what when) x
$cto :: forall what when x.
Rep (Occurrence what when) x -> Occurrence what when
$cfrom :: forall what when x.
Occurrence what when -> Rep (Occurrence what when) x
Generic)
makeOccurrence :: (OccurrenceReason what) =>
what -> EventTime b -> Occurrence what b
makeOccurrence :: what -> EventTime b -> Occurrence what b
makeOccurrence what
r EventTime b
t = (what, EventTime b) -> Occurrence what b
forall what when. (what, EventTime when) -> Occurrence what when
MkOccurrence (what
r , EventTime b
t)
getOccurrenceReason :: Occurrence what b -> what
getOccurrenceReason :: Occurrence what b -> what
getOccurrenceReason (MkOccurrence (what
r, EventTime b
t)) = what
r
getOccurrenceTime :: Occurrence what b -> EventTime b
getOccurrenceTime :: Occurrence what b -> EventTime b
getOccurrenceTime (MkOccurrence (what
r, EventTime b
t)) = EventTime b
t
instance (OccurrenceReason r, Ord b) => Ord (Occurrence r b) where
compare :: Occurrence r b -> Occurrence r b -> Ordering
compare (MkOccurrence (r
r1, EventTime b
t1)) (MkOccurrence (r
r2, EventTime b
t2))
| EventTime b
t1 EventTime b -> EventTime b -> Bool
forall a. Ord a => a -> a -> Bool
< EventTime b
t2 = Ordering
LT
| EventTime b
t1 EventTime b -> EventTime b -> Bool
forall a. Eq a => a -> a -> Bool
== EventTime b
t2 Bool -> Bool -> Bool
&& r
r1 r -> r -> Bool
forall a. Ord a => a -> a -> Bool
< r
r2 = Ordering
LT
| EventTime b
t1 EventTime b -> EventTime b -> Bool
forall a. Eq a => a -> a -> Bool
== EventTime b
t2 Bool -> Bool -> Bool
&& r
r1 r -> r -> Bool
forall a. Eq a => a -> a -> Bool
== r
r2 = Ordering
EQ
| Bool
otherwise = Ordering
GT
data CensoringReason cr or = AdminCensor | C cr | O or
deriving (CensoringReason cr or -> CensoringReason cr or -> Bool
(CensoringReason cr or -> CensoringReason cr or -> Bool)
-> (CensoringReason cr or -> CensoringReason cr or -> Bool)
-> Eq (CensoringReason cr or)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall cr or.
(Eq cr, Eq or) =>
CensoringReason cr or -> CensoringReason cr or -> Bool
/= :: CensoringReason cr or -> CensoringReason cr or -> Bool
$c/= :: forall cr or.
(Eq cr, Eq or) =>
CensoringReason cr or -> CensoringReason cr or -> Bool
== :: CensoringReason cr or -> CensoringReason cr or -> Bool
$c== :: forall cr or.
(Eq cr, Eq or) =>
CensoringReason cr or -> CensoringReason cr or -> Bool
Eq, Int -> CensoringReason cr or -> ShowS
[CensoringReason cr or] -> ShowS
CensoringReason cr or -> String
(Int -> CensoringReason cr or -> ShowS)
-> (CensoringReason cr or -> String)
-> ([CensoringReason cr or] -> ShowS)
-> Show (CensoringReason cr or)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall cr or.
(Show cr, Show or) =>
Int -> CensoringReason cr or -> ShowS
forall cr or.
(Show cr, Show or) =>
[CensoringReason cr or] -> ShowS
forall cr or. (Show cr, Show or) => CensoringReason cr or -> String
showList :: [CensoringReason cr or] -> ShowS
$cshowList :: forall cr or.
(Show cr, Show or) =>
[CensoringReason cr or] -> ShowS
show :: CensoringReason cr or -> String
$cshow :: forall cr or. (Show cr, Show or) => CensoringReason cr or -> String
showsPrec :: Int -> CensoringReason cr or -> ShowS
$cshowsPrec :: forall cr or.
(Show cr, Show or) =>
Int -> CensoringReason cr or -> ShowS
Show, (forall x. CensoringReason cr or -> Rep (CensoringReason cr or) x)
-> (forall x.
Rep (CensoringReason cr or) x -> CensoringReason cr or)
-> Generic (CensoringReason cr or)
forall x. Rep (CensoringReason cr or) x -> CensoringReason cr or
forall x. CensoringReason cr or -> Rep (CensoringReason cr or) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall cr or x.
Rep (CensoringReason cr or) x -> CensoringReason cr or
forall cr or x.
CensoringReason cr or -> Rep (CensoringReason cr or) x
$cto :: forall cr or x.
Rep (CensoringReason cr or) x -> CensoringReason cr or
$cfrom :: forall cr or x.
CensoringReason cr or -> Rep (CensoringReason cr or) x
Generic)
data CensoredOccurrence censors outcomes b = MkCensoredOccurrence {
CensoredOccurrence censors outcomes b
-> CensoringReason censors outcomes
reason :: CensoringReason censors outcomes
, CensoredOccurrence censors outcomes b
-> MaybeCensored (EventTime b)
time :: MaybeCensored ( EventTime b )}
deriving (CensoredOccurrence censors outcomes b
-> CensoredOccurrence censors outcomes b -> Bool
(CensoredOccurrence censors outcomes b
-> CensoredOccurrence censors outcomes b -> Bool)
-> (CensoredOccurrence censors outcomes b
-> CensoredOccurrence censors outcomes b -> Bool)
-> Eq (CensoredOccurrence censors outcomes b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall censors outcomes b.
(Eq censors, Eq outcomes, Eq b) =>
CensoredOccurrence censors outcomes b
-> CensoredOccurrence censors outcomes b -> Bool
/= :: CensoredOccurrence censors outcomes b
-> CensoredOccurrence censors outcomes b -> Bool
$c/= :: forall censors outcomes b.
(Eq censors, Eq outcomes, Eq b) =>
CensoredOccurrence censors outcomes b
-> CensoredOccurrence censors outcomes b -> Bool
== :: CensoredOccurrence censors outcomes b
-> CensoredOccurrence censors outcomes b -> Bool
$c== :: forall censors outcomes b.
(Eq censors, Eq outcomes, Eq b) =>
CensoredOccurrence censors outcomes b
-> CensoredOccurrence censors outcomes b -> Bool
Eq, (forall x.
CensoredOccurrence censors outcomes b
-> Rep (CensoredOccurrence censors outcomes b) x)
-> (forall x.
Rep (CensoredOccurrence censors outcomes b) x
-> CensoredOccurrence censors outcomes b)
-> Generic (CensoredOccurrence censors outcomes b)
forall x.
Rep (CensoredOccurrence censors outcomes b) x
-> CensoredOccurrence censors outcomes b
forall x.
CensoredOccurrence censors outcomes b
-> Rep (CensoredOccurrence censors outcomes b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall censors outcomes b x.
Rep (CensoredOccurrence censors outcomes b) x
-> CensoredOccurrence censors outcomes b
forall censors outcomes b x.
CensoredOccurrence censors outcomes b
-> Rep (CensoredOccurrence censors outcomes b) x
$cto :: forall censors outcomes b x.
Rep (CensoredOccurrence censors outcomes b) x
-> CensoredOccurrence censors outcomes b
$cfrom :: forall censors outcomes b x.
CensoredOccurrence censors outcomes b
-> Rep (CensoredOccurrence censors outcomes b) x
Generic)
instance (OccurrenceReason c, OccurrenceReason o, Show b) =>
Show ( CensoredOccurrence c o b ) where
show :: CensoredOccurrence c o b -> String
show (MkCensoredOccurrence CensoringReason c o
r MaybeCensored (EventTime b)
t) = String
"(" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> MaybeCensored (EventTime b) -> String
forall a. Show a => a -> String
show MaybeCensored (EventTime b)
t String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
", " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> CensoringReason c o -> String
forall a. Show a => a -> String
show CensoringReason c o
r String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
adminCensor :: EventTime b -> CensoredOccurrence c o b
adminCensor :: EventTime b -> CensoredOccurrence c o b
adminCensor EventTime b
t = CensoringReason c o
-> MaybeCensored (EventTime b) -> CensoredOccurrence c o b
forall censors outcomes b.
CensoringReason censors outcomes
-> MaybeCensored (EventTime b)
-> CensoredOccurrence censors outcomes b
MkCensoredOccurrence CensoringReason c o
forall cr or. CensoringReason cr or
AdminCensor ( EventTime b -> MaybeCensored (EventTime b)
forall a. a -> MaybeCensored a
RightCensored EventTime b
t )