-- -- Copyright © 2018 Daisee Pty Ltd - All Rights Reserved -- {-# LANGUAGE CPP #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedLists #-} {-# LANGUAGE OverloadedStrings #-} module ConfigJSONSpec(spec) where import Data.Aeson import Data.Aeson.Roundtrip import Data.Traversable import Test.Hspec import Voicebase.V2Beta.Client #if MIN_VERSION_base(4,8,0) import Data.Foldable import Data.Monoid #endif expectedDefault = Object [] configPCI = Configuration { _channels = Just ChannelSpeakers { _left = Speaker "Agent" , _right = Speaker "Caller" } , _language = EnglishAus , _detections = [RedactingPCI] } expectedPCI = Object [ ( "configuration" , Object ( [ ( "detections" , Array [ Object ( [ ( "redact" , Object ( [ ("transcripts", String "[redacted]") , ( "audio" , Object ([("tone", Number 270.0), ("gain", Number 0.5)]) ) ] ) ) , ("model", String "PCI") ] ) ] ) , ( "ingest" , Object ( [ ( "channels" , Object ( [ ("left" , Object ([("speaker", String "Agent")])) , ("right", Object ([("speaker", String "Caller")])) ] ) ) ] ) ) , ("language", String "en-AU") ] ) ) ] data ConfigSpec = ConfigSpec { label :: String , config :: Configuration , expectation :: Value } specs :: [ConfigSpec] specs = [ ConfigSpec "PCI redaction" configPCI expectedPCI ] spec :: Spec spec = describe "JSON marshalling" $ for_ specs $ \s@ConfigSpec{label, config, expectation} -> it ("meets spec for " <> label) $ runBuilder syntax config `shouldBe` Right expectation