{-# LANGUAGE CPP#-}
{-# LANGUAGE OverloadedStrings #-}
module SDL.Filesystem
  ( 
    getBasePath
  , getPrefPath
) where
import Control.Exception
import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Text (Text)
import Foreign.Marshal.Alloc
import SDL.Internal.Exception
import qualified Data.ByteString as BS
import qualified Data.Text.Encoding as Text
import qualified SDL.Raw.Filesystem as Raw
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
getBasePath :: MonadIO m => m Text
getBasePath = liftIO $ mask_ $ do
  cpath <- throwIfNull "SDL.Filesystem.getBasePath" "SDL_GetBasePath"
    Raw.getBasePath
  finally (Text.decodeUtf8 <$> BS.packCString cpath) (free cpath)
getPrefPath :: MonadIO m => Text -> Text -> m Text
getPrefPath organization application = liftIO $ mask_ $ do
  cpath <- throwIfNull "SDL.Filesystem.getPrefPath" "SDL_GetPrefPath" $
    BS.useAsCString (Text.encodeUtf8 organization) $ \org ->
      BS.useAsCString (Text.encodeUtf8 application) $ \app ->
        Raw.getPrefPath org app
  finally (Text.decodeUtf8 <$> BS.packCString cpath) (free cpath)