module Hix.Json where import qualified Data.Aeson as Aeson import Data.Aeson (FromJSON, fromJSON) import Exon (exon) import Hix.Data.Error (Error) import Hix.Data.Monad (M) import Hix.Monad (throwM) import Hix.Optparse (JsonConfig (JsonConfig)) jsonConfig :: FromJSON a => (Text -> Error) -> JsonConfig -> M a jsonConfig :: forall a. FromJSON a => (Text -> Error) -> JsonConfig -> M a jsonConfig Text -> Error consError (JsonConfig IO (Either String Value) mv) = IO (Either String Value) -> M (Either String Value) forall a. IO a -> M a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO IO (Either String Value) mv M (Either String Value) -> (Either String Value -> M a) -> M a forall a b. M a -> (a -> M b) -> M b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= \case Left String msg -> Text -> M a failure [exon|Invalid JSON: #{toText msg}|] Right Value v -> case Value -> Result a forall a. FromJSON a => Value -> Result a fromJSON Value v of Aeson.Success a a -> a -> M a forall a. a -> M a forall (f :: * -> *) a. Applicative f => a -> f a pure a a Aeson.Error String err -> Text -> M a failure [exon|Invalid JSON: #{toText err} #{show v}|] where failure :: Text -> M a failure = Error -> M a forall a. Error -> M a throwM (Error -> M a) -> (Text -> Error) -> Text -> M a forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> Error consError jsonConfigE :: FromJSON a => (Text -> Error) -> Either a JsonConfig -> M a jsonConfigE :: forall a. FromJSON a => (Text -> Error) -> Either a JsonConfig -> M a jsonConfigE Text -> Error consError = (a -> M a) -> (JsonConfig -> M a) -> Either a JsonConfig -> M a forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either a -> M a forall a. a -> M a forall (f :: * -> *) a. Applicative f => a -> f a pure ((Text -> Error) -> JsonConfig -> M a forall a. FromJSON a => (Text -> Error) -> JsonConfig -> M a jsonConfig Text -> Error consError)