{-# LANGUAGE OverloadedStrings #-} module Main where 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) data MainOptions = MainOptions { user_id :: Maybe UserID, token :: Maybe AuthToken, 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 <*> 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 result <- transcribeBytes userId bearToken "en-US" (LazyByteFile bytes file mime) putStrLn . show $ result