module Sound.Sc3.Server.Nrt.Stat where
import Sound.Osc.Datum
import Sound.Osc.Packet
import Sound.Sc3.Common.Base
import Sound.Sc3.Server.Nrt
type Nrt_Stat =
( (String, Time)
, (String, Int)
, (String, Int)
, (String, [(String, Int)])
)
nrt_stat_param :: (String, String, String, String)
nrt_stat_param :: (String, String, String, String)
nrt_stat_param = (String
"duration", String
"# bundles", String
"# messages", String
"command set")
nrt_stat :: Nrt -> Nrt_Stat
nrt_stat :: Nrt -> Nrt_Stat
nrt_stat (Nrt [BundleOf Message]
b_seq) =
let b_msg :: [[Message]]
b_msg = (BundleOf Message -> [Message])
-> [BundleOf Message] -> [[Message]]
forall a b. (a -> b) -> [a] -> [b]
map BundleOf Message -> [Message]
forall t. BundleOf t -> [t]
bundleMessages [BundleOf Message]
b_seq
in (String, String, String, String)
-> (Time, Int, Int, [(String, Int)]) -> Nrt_Stat
forall a b c d e f g h.
(a, b, c, d) -> (e, f, g, h) -> ((a, e), (b, f), (c, g), (d, h))
p4_zip
(String, String, String, String)
nrt_stat_param
( BundleOf Message -> Time
forall t. BundleOf t -> Time
bundleTime ([BundleOf Message] -> BundleOf Message
forall a. HasCallStack => [a] -> a
last [BundleOf Message]
b_seq)
, [BundleOf Message] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [BundleOf Message]
b_seq
, [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (([Message] -> Int) -> [[Message]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map [Message] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Message]]
b_msg)
, [String] -> [(String, Int)]
forall a. Ord a => [a] -> [(a, Int)]
histogram (([Message] -> [String]) -> [[Message]] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((Message -> String) -> [Message] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Message -> String
messageAddress) [[Message]]
b_msg)
)