{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}

module Test.Sandwich.Types.TestTimer where

import Control.Concurrent
import Data.Aeson as A
import Data.Aeson.TH as A
import qualified Data.List as L
import Data.Sequence
import qualified Data.Text as T
import Data.Time.Clock.POSIX
import Lens.Micro.TH
import System.IO
import Test.Sandwich.Types.Spec
import Test.Sandwich.Types.TestTimer.LensRules (testTimerLensRules)


-- * SpeedScope types

data SpeedScopeFrame = SpeedScopeFrame {
  SpeedScopeFrame -> Text
_name :: T.Text
  } deriving (Int -> SpeedScopeFrame -> ShowS
[SpeedScopeFrame] -> ShowS
SpeedScopeFrame -> String
(Int -> SpeedScopeFrame -> ShowS)
-> (SpeedScopeFrame -> String)
-> ([SpeedScopeFrame] -> ShowS)
-> Show SpeedScopeFrame
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SpeedScopeFrame -> ShowS
showsPrec :: Int -> SpeedScopeFrame -> ShowS
$cshow :: SpeedScopeFrame -> String
show :: SpeedScopeFrame -> String
$cshowList :: [SpeedScopeFrame] -> ShowS
showList :: [SpeedScopeFrame] -> ShowS
Show, SpeedScopeFrame -> SpeedScopeFrame -> Bool
(SpeedScopeFrame -> SpeedScopeFrame -> Bool)
-> (SpeedScopeFrame -> SpeedScopeFrame -> Bool)
-> Eq SpeedScopeFrame
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SpeedScopeFrame -> SpeedScopeFrame -> Bool
== :: SpeedScopeFrame -> SpeedScopeFrame -> Bool
$c/= :: SpeedScopeFrame -> SpeedScopeFrame -> Bool
/= :: SpeedScopeFrame -> SpeedScopeFrame -> Bool
Eq)
$(deriveJSON (A.defaultOptions {
                 A.fieldLabelModifier = L.drop 1
                 , A.sumEncoding = A.UntaggedValue
                 }) ''SpeedScopeFrame)
$(makeLensesWith testTimerLensRules ''SpeedScopeFrame)

data SpeedScopeShared = SpeedScopeShared {
  SpeedScopeShared -> Seq SpeedScopeFrame
_frames :: Seq SpeedScopeFrame
  } deriving Int -> SpeedScopeShared -> ShowS
[SpeedScopeShared] -> ShowS
SpeedScopeShared -> String
(Int -> SpeedScopeShared -> ShowS)
-> (SpeedScopeShared -> String)
-> ([SpeedScopeShared] -> ShowS)
-> Show SpeedScopeShared
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SpeedScopeShared -> ShowS
showsPrec :: Int -> SpeedScopeShared -> ShowS
$cshow :: SpeedScopeShared -> String
show :: SpeedScopeShared -> String
$cshowList :: [SpeedScopeShared] -> ShowS
showList :: [SpeedScopeShared] -> ShowS
Show
$(deriveJSON (A.defaultOptions {
                 A.fieldLabelModifier = L.drop 1
                 , A.sumEncoding = A.UntaggedValue
                 }) ''SpeedScopeShared)
$(makeLensesWith testTimerLensRules ''SpeedScopeShared)

data SpeedScopeEventType = SpeedScopeEventTypeOpen | SpeedScopeEventTypeClose
  deriving (Int -> SpeedScopeEventType -> ShowS
[SpeedScopeEventType] -> ShowS
SpeedScopeEventType -> String
(Int -> SpeedScopeEventType -> ShowS)
-> (SpeedScopeEventType -> String)
-> ([SpeedScopeEventType] -> ShowS)
-> Show SpeedScopeEventType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SpeedScopeEventType -> ShowS
showsPrec :: Int -> SpeedScopeEventType -> ShowS
$cshow :: SpeedScopeEventType -> String
show :: SpeedScopeEventType -> String
$cshowList :: [SpeedScopeEventType] -> ShowS
showList :: [SpeedScopeEventType] -> ShowS
Show, SpeedScopeEventType -> SpeedScopeEventType -> Bool
(SpeedScopeEventType -> SpeedScopeEventType -> Bool)
-> (SpeedScopeEventType -> SpeedScopeEventType -> Bool)
-> Eq SpeedScopeEventType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SpeedScopeEventType -> SpeedScopeEventType -> Bool
== :: SpeedScopeEventType -> SpeedScopeEventType -> Bool
$c/= :: SpeedScopeEventType -> SpeedScopeEventType -> Bool
/= :: SpeedScopeEventType -> SpeedScopeEventType -> Bool
Eq)
$(deriveJSON (A.defaultOptions {
                 A.constructorTagModifier = L.take 1 . L.drop (L.length ("SpeedScopeEventType" :: String))
                 , A.sumEncoding = A.UntaggedValue
                 }) ''SpeedScopeEventType)

data SpeedScopeEvent = SpeedScopeEvent {
  SpeedScopeEvent -> SpeedScopeEventType
_typ :: SpeedScopeEventType
  , SpeedScopeEvent -> Int
_frame :: Int
  , SpeedScopeEvent -> POSIXTime
_at :: POSIXTime
  } deriving Int -> SpeedScopeEvent -> ShowS
[SpeedScopeEvent] -> ShowS
SpeedScopeEvent -> String
(Int -> SpeedScopeEvent -> ShowS)
-> (SpeedScopeEvent -> String)
-> ([SpeedScopeEvent] -> ShowS)
-> Show SpeedScopeEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SpeedScopeEvent -> ShowS
showsPrec :: Int -> SpeedScopeEvent -> ShowS
$cshow :: SpeedScopeEvent -> String
show :: SpeedScopeEvent -> String
$cshowList :: [SpeedScopeEvent] -> ShowS
showList :: [SpeedScopeEvent] -> ShowS
Show
$(deriveJSON (A.defaultOptions {
                 A.fieldLabelModifier = \x -> case x of
                     "_typ" -> "type"
                     _ -> L.drop 1 x
                 , A.sumEncoding = A.UntaggedValue
                 }) ''SpeedScopeEvent)
$(makeLensesWith testTimerLensRules ''SpeedScopeEvent)

data SpeedScopeProfile = SpeedScopeProfile {
  SpeedScopeProfile -> Text
_typ :: T.Text
  , SpeedScopeProfile -> Text
_name :: T.Text
  , SpeedScopeProfile -> Text
_unit :: T.Text
  , SpeedScopeProfile -> POSIXTime
_startValue :: POSIXTime
  , SpeedScopeProfile -> POSIXTime
_endValue :: POSIXTime
  , SpeedScopeProfile -> Seq SpeedScopeEvent
_events :: Seq SpeedScopeEvent
  } deriving Int -> SpeedScopeProfile -> ShowS
[SpeedScopeProfile] -> ShowS
SpeedScopeProfile -> String
(Int -> SpeedScopeProfile -> ShowS)
-> (SpeedScopeProfile -> String)
-> ([SpeedScopeProfile] -> ShowS)
-> Show SpeedScopeProfile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SpeedScopeProfile -> ShowS
showsPrec :: Int -> SpeedScopeProfile -> ShowS
$cshow :: SpeedScopeProfile -> String
show :: SpeedScopeProfile -> String
$cshowList :: [SpeedScopeProfile] -> ShowS
showList :: [SpeedScopeProfile] -> ShowS
Show
$(deriveJSON (A.defaultOptions {
                 A.fieldLabelModifier = \x -> case x of
                     "_typ" -> "type"
                     _ -> L.drop 1 x
                 , A.sumEncoding = A.UntaggedValue
                 }) ''SpeedScopeProfile)
$(makeLensesWith testTimerLensRules ''SpeedScopeProfile)

data SpeedScopeFile = SpeedScopeFile {
  SpeedScopeFile -> Text
_exporter :: T.Text
  , SpeedScopeFile -> Text
_name :: T.Text
  , SpeedScopeFile -> Int
_activeProfileIndex :: Int
  , SpeedScopeFile -> Text
_schema :: T.Text
  , SpeedScopeFile -> SpeedScopeShared
_shared :: SpeedScopeShared
  , SpeedScopeFile -> [SpeedScopeProfile]
_profiles :: [SpeedScopeProfile]
  } deriving Int -> SpeedScopeFile -> ShowS
[SpeedScopeFile] -> ShowS
SpeedScopeFile -> String
(Int -> SpeedScopeFile -> ShowS)
-> (SpeedScopeFile -> String)
-> ([SpeedScopeFile] -> ShowS)
-> Show SpeedScopeFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SpeedScopeFile -> ShowS
showsPrec :: Int -> SpeedScopeFile -> ShowS
$cshow :: SpeedScopeFile -> String
show :: SpeedScopeFile -> String
$cshowList :: [SpeedScopeFile] -> ShowS
showList :: [SpeedScopeFile] -> ShowS
Show
$(deriveJSON (A.defaultOptions {
                 A.fieldLabelModifier = \x -> case x of
                     "_schema" -> "$schema"
                     _ -> L.drop 1 x
                 , A.sumEncoding = A.UntaggedValue
                 }) ''SpeedScopeFile)
$(makeLensesWith testTimerLensRules ''SpeedScopeFile)

emptySpeedScopeFile :: SpeedScopeFile
emptySpeedScopeFile =
  SpeedScopeFile {
    $sel:_exporter:SpeedScopeFile :: Text
_exporter = Text
"sandwich-test-exporter"
    , $sel:_name:SpeedScopeFile :: Text
_name = Text
"sandwich-test"
    , $sel:_activeProfileIndex:SpeedScopeFile :: Int
_activeProfileIndex = Int
0
    , $sel:_schema:SpeedScopeFile :: Text
_schema = Text
"https://www.speedscope.app/file-format-schema.json"
    , $sel:_shared:SpeedScopeFile :: SpeedScopeShared
_shared = SpeedScopeShared {
        $sel:_frames:SpeedScopeShared :: Seq SpeedScopeFrame
_frames = Seq SpeedScopeFrame
forall a. Monoid a => a
mempty
        }
    , $sel:_profiles:SpeedScopeFile :: [SpeedScopeProfile]
_profiles = []
    }

newProfile :: T.Text -> POSIXTime -> SpeedScopeProfile
newProfile :: Text -> POSIXTime -> SpeedScopeProfile
newProfile Text
profileName POSIXTime
startTime = SpeedScopeProfile {
  $sel:_typ:SpeedScopeProfile :: Text
_typ = Text
"evented"
  , $sel:_name:SpeedScopeProfile :: Text
_name = Text
profileName
  , $sel:_unit:SpeedScopeProfile :: Text
_unit = Text
"seconds"
  , $sel:_startValue:SpeedScopeProfile :: POSIXTime
_startValue = POSIXTime
startTime
  , $sel:_endValue:SpeedScopeProfile :: POSIXTime
_endValue = POSIXTime
startTime
  , $sel:_events:SpeedScopeProfile :: Seq SpeedScopeEvent
_events = Seq SpeedScopeEvent
forall a. Monoid a => a
mempty
  }

-- * Main type

data TestTimer = SpeedScopeTestTimer {
  TestTimer -> String
testTimerBasePath :: FilePath
  , TestTimer -> Maybe Handle
testTimerHandle :: Maybe Handle
  , TestTimer -> MVar SpeedScopeFile
testTimerSpeedScopeFile :: MVar SpeedScopeFile
  } | NullTestTimer

-- * Labels and classes

defaultProfileName :: T.Text
defaultProfileName :: Text
defaultProfileName = Text
"default"

class HasTestTimer context where
  getTestTimer :: context -> TestTimer

testTimerProfile :: Label "testTimerProfile" TestTimerProfile
testTimerProfile = Label "testTimerProfile" TestTimerProfile
forall {k} (l :: Symbol) (a :: k). Label l a
Label :: Label "testTimerProfile" TestTimerProfile

newtype TestTimerProfile = TestTimerProfile T.Text