{-# LANGUAGE OverloadedStrings #-} module Main where import Control.Monad.Logger(LoggingT(..), runStdoutLoggingT, logInfoNS, logDebugNS, logWarnNS, logErrorNS, MonadLogger) import Network.Mime(defaultMimeLookup) import Options import qualified Data.ByteString.Lazy as LBS import Data.Digest.Pure.SHA import Speechmatics.Client import Network.Mime(MimeType) import Data.Text(pack, Text) import Data.Aeson (decode) data MainOptions = MainOptions { user_id :: Maybe UserID, token :: Maybe String, targetFile :: Maybe FilePath } instance Options MainOptions where defineOptions = pure MainOptions <*> simpleOption "userId" Nothing "The user id obtained from speechmatics" <*> simpleOption "token" Nothing "The bearer token obtained from speechmatics" <*> simpleOption "file" Nothing "The file to be posted" main :: IO () main = runCommand $ \opts args -> do case withBearAndFile <$> user_id opts <*> (Just . pack <$> token opts) <*> targetFile opts of Nothing -> print "wrong options, see --help" Just compute -> compute withBearAndFile :: UserID -> AuthToken -> FilePath -> IO() withBearAndFile userId bearToken file = do -- result <- transcribeFile bearToken file bytes <- LBS.readFile file let mime = (defaultMimeLookup "d.mp3") print mime print . sha256 $ bytes case decode "{ \"type\": \"transcription\", \"transcription_config\": { \"language\": \"en-AU\", \"diarization\": \"channel\", \"channel_diarization_labels\": [\"Agent\", \"Caller\"] } }" of Just json -> do result <- runStdoutLoggingT $ transcribeBytes (ByteConfig (Location JsonV2 "http://192.168.38.91:8082/v1/user/" userId Nothing) -- "{ \"type\": \"transcription\", \"transcription_config\": { \"language\": \"en-AU\", \"diarization\": \"channel\", \"channel_diarization_labels\": [\"Agent\", \"Caller\"] } }") json) (LoadedFile bytes file mime) putStrLn . show $ result Nothing -> return ()