module Sound.Sc3.Common.SoundFile where
import System.Environment 
import System.IO.Unsafe 
import System.Process 
import System.Directory 
import System.FilePath 
import qualified Sound.Sc3.Common.Base 
findFileFromDirectory :: String -> String -> IO (Maybe String)
findFileFromDirectory :: String -> String -> IO (Maybe String)
findFileFromDirectory String
dir String
fn = do
  String
r <- String -> [String] -> String -> IO String
System.Process.readProcess String
"find" [String
dir, String
"-name", String
fn] String
""
  case String -> [String]
lines String
r of
    [] -> Maybe String -> IO (Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing
    [String
r0] -> Maybe String -> IO (Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Maybe String
forall a. a -> Maybe a
Just String
r0)
    [String]
_ -> String -> IO (Maybe String)
forall a. HasCallStack => String -> a
error String
"findFileFromDirectory: multiple files?"
findFileAtOrFromDirectory :: String -> String -> IO (Maybe String)
findFileAtOrFromDirectory :: String -> String -> IO (Maybe String)
findFileAtOrFromDirectory String
dir String
fn = do
  Bool
isAtDir <- String -> IO Bool
doesFileExist (String
dir String -> String -> String
</> String
fn)
  if Bool
isAtDir then Maybe String -> IO (Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Maybe String
forall a. a -> Maybe a
Just (String
dir String -> String -> String
</> String
fn)) else String -> String -> IO (Maybe String)
findFileFromDirectory String
dir String
fn
findFileAtOrFromPath :: [FilePath] -> FilePath -> IO (Maybe FilePath)
findFileAtOrFromPath :: [String] -> String -> IO (Maybe String)
findFileAtOrFromPath [String]
path String
fn =
  case [String]
path of
    [] -> Maybe String -> IO (Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing
    String
dir : [String]
path' -> do
      Maybe String
m <- String -> String -> IO (Maybe String)
findFileAtOrFromDirectory String
dir String
fn
      case Maybe String
m of
        Just String
r -> Maybe String -> IO (Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Maybe String
forall a. a -> Maybe a
Just String
r)
        Maybe String
Nothing -> [String] -> String -> IO (Maybe String)
findFileAtOrFromPath [String]
path' String
fn
sfDir :: IO FilePath
sfDir :: IO String
sfDir = String -> IO String
getEnv String
"SFDIR"
sfPath :: IO FilePath
sfPath :: IO String
sfPath = String -> IO String
getEnv String
"SFPATH"
sfFindFile :: FilePath -> IO (Maybe FilePath)
sfFindFile :: String -> IO (Maybe String)
sfFindFile String
fn = do
  String
dir <- IO String
sfDir
  [String]
path <- (String -> [String]) -> IO String -> IO [String]
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Char -> String -> [String]
Sound.Sc3.Common.Base.string_split_at_char Char
':') IO String
sfPath
  Bool
isFn <- String -> IO Bool
doesFileExist String
fn
  Bool
isDir <- String -> IO Bool
doesFileExist (String
dir String -> String -> String
</> String
fn)
  if Bool
isFn then Maybe String -> IO (Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Maybe String
forall a. a -> Maybe a
Just String
fn) else if Bool
isDir then Maybe String -> IO (Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Maybe String
forall a. a -> Maybe a
Just (String
dir String -> String -> String
</> String
fn)) else [String] -> String -> IO (Maybe String)
findFileAtOrFromPath [String]
path String
fn
sfResolveFile :: FilePath -> IO FilePath
sfResolveFile :: String -> IO String
sfResolveFile String
fn = do
  Maybe String
m <- String -> IO (Maybe String)
sfFindFile String
fn
  case Maybe String
m of
    Maybe String
Nothing -> String -> IO String
forall a. HasCallStack => String -> a
error (String
"sfResolveFile: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fn)
    Just String
r -> String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
r
sfResolve :: FilePath -> FilePath
sfResolve :: String -> String
sfResolve = IO String -> String
forall a. IO a -> a
unsafePerformIO (IO String -> String) -> (String -> IO String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO String
sfResolveFile
sfNumChannels :: FilePath -> IO Int
sfNumChannels :: String -> IO Int
sfNumChannels String
fn = (String -> Int) -> IO String -> IO Int
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Int
forall a. Read a => String -> a
read (String -> [String] -> String -> IO String
System.Process.readProcess String
"soxi" [String
"-c", String
fn] String
"")
sfSampleRate :: FilePath -> IO Int
sfSampleRate :: String -> IO Int
sfSampleRate String
fn = (String -> Int) -> IO String -> IO Int
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Int
forall a. Read a => String -> a
read (String -> [String] -> String -> IO String
System.Process.readProcess String
"soxi" [String
"-r", String
fn] String
"")
sfFrameCount :: FilePath -> IO Int
sfFrameCount :: String -> IO Int
sfFrameCount String
fn = (String -> Int) -> IO String -> IO Int
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Int
forall a. Read a => String -> a
read (String -> [String] -> String -> IO String
System.Process.readProcess String
"soxi" [String
"-s", String
fn] String
"")
sfMetadata :: FilePath -> IO (Int, Int, Int)
sfMetadata :: String -> IO (Int, Int, Int)
sfMetadata String
fn = do
  Int
nc <- String -> IO Int
sfNumChannels String
fn
  Int
sr <- String -> IO Int
sfSampleRate String
fn
  Int
nf <- String -> IO Int
sfFrameCount String
fn
  (Int, Int, Int) -> IO (Int, Int, Int)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
nc, Int
sr, Int
nf)
sfInfo :: FilePath -> (Int, Int, Int)
sfInfo :: String -> (Int, Int, Int)
sfInfo = IO (Int, Int, Int) -> (Int, Int, Int)
forall a. IO a -> a
unsafePerformIO (IO (Int, Int, Int) -> (Int, Int, Int))
-> (String -> IO (Int, Int, Int)) -> String -> (Int, Int, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO (Int, Int, Int)
sfMetadata