summaryrefslogtreecommitdiff
path: root/events/src/Events/Types.hs
blob: 55e7a5a7834746fc33e27ec5e460af777e05cb06 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
{-# LANGUAGE TemplateHaskell #-}

module Events.Types
       ( TimeRange(..), rangeStart, rangeDuration
       , Event(..), payload, occursWithin
       , SpecCtx(..), ctxVars
       , Spec
       , module Data.Aeson
       , module Data.Time.Clock
       , module Data.Default.Class
       ) where

import Control.Lens.TH
  
import Data.Aeson (Object)

import Data.Time.Clock

import Control.Monad.Reader
import ListT (ListT)
import qualified ListT as ListT

import Data.Default.Class

import Data.Monoid
import Control.Monad.Fix
import Control.Lens
import Data.Maybe

data TimeRange = TimeRange
                 { _rangeStart :: UTCTime
                 , _rangeDuration :: NominalDiffTime
                 }
makeLenses ''TimeRange

data Event = Event
             { _payload :: Object
             , _occursWithin :: TimeRange -> Bool
             }
makeLenses ''Event

data SpecCtx = SpecCtx
               { _ctxVars :: Object
               , _ctxEvents :: [Event]
               }
makeLenses ''SpecCtx

instance Default SpecCtx where
  def = SpecCtx
        { _ctxVars = mempty
        , _ctxEvents = mempty
        }

type Spec m a = ListT (ReaderT SpecCtx m) a

interpret :: MonadFix m => Spec m (Maybe Event) -> m [Event]
interpret x = catMaybes <$> mfix x'
  where
    x' = runReaderT (ListT.toList x) . flip (set ctxEvents) def . catMaybes