{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
module Data.Medea.Loader
( LoaderError (..),
buildSchema,
loadSchemaFromFile,
loadSchemaFromHandle,
)
where
import Control.Monad.Except (MonadError (..), runExcept)
import Control.Monad.IO.Class (MonadIO (..))
import Data.ByteString (ByteString, hGetContents, readFile)
import Data.Medea.Analysis
( AnalysisError (..),
compileSchemata,
)
import Data.Medea.Parser.Primitive (toText, unwrap)
import qualified Data.Medea.Parser.Spec.Schemata as Schemata
import Data.Medea.Parser.Types (ParseError)
import Data.Medea.Schema (Schema (..))
import Data.Text (Text)
import Data.Text.Encoding (decodeUtf8')
import System.IO (Handle)
import Text.Megaparsec (ParseErrorBundle, parse)
import Prelude hiding (readFile)
data LoaderError
=
NotUtf8
|
ParsingFailed
!(ParseErrorBundle Text ParseError)
|
StartSchemaMissing
|
SelfTypingSchema
|
MultipleSchemaDefinition
{-# UNPACK #-} !Text
|
MissingSchemaDefinition
{-# UNPACK #-} !Text
{-# UNPACK #-} !Text
|
SchemaNameReserved
{-# UNPACK #-} !Text
|
IsolatedSchemata
{-# UNPACK #-} !Text
|
MissingPropSchemaDefinition
{-# UNPACK #-} !Text
{-# UNPACK #-} !Text
|
MinimumLengthGreaterThanMaximum
{-# UNPACK #-} !Text
|
MultiplePropSchemaDefinition
{-# UNPACK #-} !Text
{-# UNPACK #-} !Text
|
MissingListSchemaDefinition
{-# UNPACK #-} !Text
{-# UNPACK #-} !Text
|
MissingTupleSchemaDefinition
{-# UNPACK #-} !Text
{-# UNPACK #-} !Text
|
PropertySpecWithoutObjectType
{-# UNPACK #-} !Text
|
ListSpecWithoutArrayType
{-# UNPACK #-} !Text
|
TupleSpecWithoutArrayType
{-# UNPACK #-} !Text
|
StringSpecWithoutStringType
{-# UNPACK #-} !Text
deriving stock (Eq, Show)
buildSchema ::
(MonadError LoaderError m) =>
ByteString ->
m Schema
buildSchema bs = do
utf8 <- parseUtf8 bs
spec <- fromUtf8 ":memory:" utf8
analyze spec
loadSchemaFromFile ::
(MonadIO m, MonadError LoaderError m) =>
FilePath ->
m Schema
loadSchemaFromFile fp = do
contents <- liftIO . readFile $ fp
utf8 <- parseUtf8 contents
spec <- fromUtf8 fp utf8
analyze spec
loadSchemaFromHandle ::
(MonadIO m, MonadError LoaderError m) =>
Handle ->
m Schema
loadSchemaFromHandle h = do
contents <- liftIO . hGetContents $ h
utf8 <- parseUtf8 contents
spec <- fromUtf8 (show h) utf8
analyze spec
parseUtf8 ::
(MonadError LoaderError m) =>
ByteString ->
m Text
parseUtf8 = either (const (throwError NotUtf8)) pure . decodeUtf8'
fromUtf8 ::
(MonadError LoaderError m) =>
String ->
Text ->
m Schemata.Specification
fromUtf8 sourceName utf8 =
case parse Schemata.parseSpecification sourceName utf8 of
Left err -> throwError . ParsingFailed $ err
Right scm -> pure scm
analyze ::
(MonadError LoaderError m) =>
Schemata.Specification ->
m Schema
analyze scm = case runExcept $ compileSchemata scm of
Left (DuplicateSchemaName ident) ->
throwError $ MultipleSchemaDefinition (toText ident)
Left NoStartSchema -> throwError StartSchemaMissing
Left (DanglingTypeReference danglingRef parSchema) ->
throwError $ MissingSchemaDefinition (toText danglingRef) (toText parSchema)
Left TypeRelationIsCyclic -> throwError SelfTypingSchema
Left (ReservedDefined ident) ->
throwError $ SchemaNameReserved (toText ident)
Left (DefinedButNotUsed ident) ->
throwError $ IsolatedSchemata (toText ident)
Left (DanglingTypeRefProp danglingRef parSchema) ->
throwError $ MissingPropSchemaDefinition (toText danglingRef) (toText parSchema)
Left (MinMoreThanMax ident) ->
throwError $ MinimumLengthGreaterThanMaximum (toText ident)
Left (DuplicatePropName ident prop) ->
throwError $
MultiplePropSchemaDefinition (toText ident) (unwrap prop)
Left (DanglingTypeRefList danglingRef parSchema) ->
throwError $ MissingListSchemaDefinition (toText danglingRef) (toText parSchema)
Left (DanglingTypeRefTuple danglingRef parSchema) ->
throwError $ MissingTupleSchemaDefinition (toText danglingRef) (toText parSchema)
Left (PropertyWithoutObject schema) ->
throwError $ PropertySpecWithoutObjectType (toText schema)
Left (ListWithoutArray schema) ->
throwError $ ListSpecWithoutArrayType (toText schema)
Left (TupleWithoutArray schema) ->
throwError $ TupleSpecWithoutArrayType (toText schema)
Left (StringValsWithoutString schema) ->
throwError $ StringSpecWithoutStringType (toText schema)
Right g -> pure . Schema $ g