{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE NoFieldSelectors #-} module WikiMusic.SSR.Config (readConfig) where import Data.Text (unpack) import Relude import Toml import WikiMusic.SSR.Model.Config readConfig :: (MonadIO m) => Text -> m (Either Text AppConfig) readConfig :: forall (m :: * -> *). MonadIO m => Text -> m (Either Text AppConfig) readConfig Text filePath = do Either [TomlDecodeError] AppConfig parseResult <- IO (Either [TomlDecodeError] AppConfig) -> m (Either [TomlDecodeError] AppConfig) forall a. IO a -> m a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO (Either [TomlDecodeError] AppConfig) -> m (Either [TomlDecodeError] AppConfig)) -> IO (Either [TomlDecodeError] AppConfig) -> m (Either [TomlDecodeError] AppConfig) forall a b. (a -> b) -> a -> b $ TomlCodec AppConfig -> FilePath -> IO (Either [TomlDecodeError] AppConfig) forall a (m :: * -> *). MonadIO m => TomlCodec a -> FilePath -> m (Either [TomlDecodeError] a) decodeFileEither TomlCodec AppConfig appConfigCodec (Text -> FilePath unpack Text filePath) case Either [TomlDecodeError] AppConfig parseResult of Left [TomlDecodeError] e -> Either Text AppConfig -> m (Either Text AppConfig) forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure (Either Text AppConfig -> m (Either Text AppConfig)) -> (Text -> Either Text AppConfig) -> Text -> m (Either Text AppConfig) forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> Either Text AppConfig forall a b. a -> Either a b Left (Text -> m (Either Text AppConfig)) -> Text -> m (Either Text AppConfig) forall a b. (a -> b) -> a -> b $ [TomlDecodeError] -> Text prettyTomlDecodeErrors [TomlDecodeError] e Right AppConfig r -> Either Text AppConfig -> m (Either Text AppConfig) forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure (Either Text AppConfig -> m (Either Text AppConfig)) -> (AppConfig -> Either Text AppConfig) -> AppConfig -> m (Either Text AppConfig) forall b c a. (b -> c) -> (a -> b) -> a -> c . AppConfig -> Either Text AppConfig forall a b. b -> Either a b Right (AppConfig -> m (Either Text AppConfig)) -> AppConfig -> m (Either Text AppConfig) forall a b. (a -> b) -> a -> b $ AppConfig r