module System.REPL.Config (
readConfigFile,
readConfigJSON,
readConfigShow,
NoParseError(..),
) where
import Prelude hiding ((++), FilePath)
import qualified Prelude as Pr
import Control.Monad.Catch
import Control.Monad.IO.Class
import Data.Aeson
import qualified Data.ByteString.Lazy as BL
import Data.Default
import Data.Functor.Monadic
import Data.ListLike (ListLike(append), StringLike(fromString))
import Data.Text.Lazy.Encoding (decodeUtf8, encodeUtf8)
import qualified Data.Text.Lazy as T
import Data.Typeable
import qualified Filesystem.Path.CurrentOS as Fp
import System.Directory
import Text.Read (readMaybe)
data NoParseError = NoParseError T.Text deriving (Show, Eq, Read, Typeable)
instance Exception NoParseError
noParseError :: Fp.FilePath -> NoParseError
noParseError = NoParseError . T.pack . Fp.encodeString
readConfigShow :: forall m a.
(MonadThrow m, Functor m, MonadIO m, Default a, Show a,
Read a)
=> Fp.FilePath
-> m a
readConfigShow path = readConfigFile path readEither showBL
where
showBL = encodeUtf8 . T.pack . show
readEither = maybe (Left $ noParseError path) Right . readMaybe . T.unpack . decodeUtf8
readConfigJSON :: forall m a.
(MonadThrow m, Functor m, MonadIO m, Default a, ToJSON a,
FromJSON a)
=> Fp.FilePath
-> m a
readConfigJSON path = readConfigFile path decodeEither encode
where
decodeEither = maybe (Left $ noParseError path) Right . decode
readConfigFile :: forall e m a.
(MonadThrow m, Functor m, MonadIO m, Default a, Exception e)
=> Fp.FilePath
-> (BL.ByteString -> Either e a)
-> (a -> BL.ByteString)
-> m a
readConfigFile path parser writer = do
let pathT = Fp.encodeString path
liftIO $ createDirectoryIfMissing True $ Fp.encodeString $ Fp.parent path
exists <- liftIO $ doesFileExist $ Fp.encodeString path
content <- if not exists then do liftIO $ BL.writeFile pathT (writer (def :: a))
return $ Right def
else liftIO (BL.readFile pathT) >$> parser
either throwM return content