{-# LANGUAGE OverloadedStrings #-}
module OpenAPI.Generate.Internal.Unknown
( warnAboutUnknownWhiteListedOrOpaqueSchemas,
warnAboutUnknownOperations,
)
where
import Control.Monad
import qualified Data.List as L
import qualified Data.Maybe as Maybe
import qualified Data.Ord as Ord
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
import qualified OpenAPI.Generate.Monad as OAM
import qualified OpenAPI.Generate.OptParse as OAO
import qualified OpenAPI.Generate.Types as OAT
import qualified OpenAPI.Generate.Types.Schema as OAS
warnAboutUnknownOperations :: [(Text, OAT.PathItemObject)] -> OAM.Generator ()
warnAboutUnknownOperations :: [(Text, PathItemObject)] -> Generator ()
warnAboutUnknownOperations [(Text, PathItemObject)]
operationDefinitions = do
let getAllOperationObjectsFromPathItemObject :: PathItemObject -> [Maybe OperationObject]
getAllOperationObjectsFromPathItemObject = ([PathItemObject -> Maybe OperationObject
OAT.pathItemObjectGet, PathItemObject -> Maybe OperationObject
OAT.pathItemObjectPut, PathItemObject -> Maybe OperationObject
OAT.pathItemObjectPost, PathItemObject -> Maybe OperationObject
OAT.pathItemObjectDelete, PathItemObject -> Maybe OperationObject
OAT.pathItemObjectOptions, PathItemObject -> Maybe OperationObject
OAT.pathItemObjectHead, PathItemObject -> Maybe OperationObject
OAT.pathItemObjectPatch, PathItemObject -> Maybe OperationObject
OAT.pathItemObjectTrace] [PathItemObject -> Maybe OperationObject]
-> [PathItemObject] -> [Maybe OperationObject]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>) ([PathItemObject] -> [Maybe OperationObject])
-> (PathItemObject -> [PathItemObject])
-> PathItemObject
-> [Maybe OperationObject]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PathItemObject -> [PathItemObject]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
operationIds :: [Text]
operationIds =
(OperationObject -> Maybe Text) -> [OperationObject] -> [Text]
forall a b. (a -> Maybe b) -> [a] -> [b]
Maybe.mapMaybe OperationObject -> Maybe Text
OAT.operationObjectOperationId ([OperationObject] -> [Text]) -> [OperationObject] -> [Text]
forall a b. (a -> b) -> a -> b
$
[Maybe OperationObject] -> [OperationObject]
forall a. [Maybe a] -> [a]
Maybe.catMaybes ([Maybe OperationObject] -> [OperationObject])
-> [Maybe OperationObject] -> [OperationObject]
forall a b. (a -> b) -> a -> b
$
[(Text, PathItemObject)]
operationDefinitions [(Text, PathItemObject)]
-> ((Text, PathItemObject) -> [Maybe OperationObject])
-> [Maybe OperationObject]
forall a b. [a] -> (a -> [b]) -> [b]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= PathItemObject -> [Maybe OperationObject]
getAllOperationObjectsFromPathItemObject (PathItemObject -> [Maybe OperationObject])
-> ((Text, PathItemObject) -> PathItemObject)
-> (Text, PathItemObject)
-> [Maybe OperationObject]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, PathItemObject) -> PathItemObject
forall a b. (a, b) -> b
snd
[Text]
operationsToGenerate <- (Settings -> [Text]) -> Generator [Text]
forall a. (Settings -> a) -> Generator a
OAM.getSetting Settings -> [Text]
OAO.settingOperationsToGenerate
(Text -> Text -> Text) -> [Text] -> [Text] -> Generator ()
printWarningIfUnknown (\Text
operationId Text
proposedOptions -> Text
"The operation '" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
operationId Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"' which is listed for generation does not appear in the provided OpenAPI specification. " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
proposedOptions) [Text]
operationIds [Text]
operationsToGenerate
warnAboutUnknownWhiteListedOrOpaqueSchemas :: [(Text, OAS.Schema)] -> OAM.Generator ()
warnAboutUnknownWhiteListedOrOpaqueSchemas :: [(Text, Schema)] -> Generator ()
warnAboutUnknownWhiteListedOrOpaqueSchemas [(Text, Schema)]
schemaDefinitions = do
let schemaNames :: [Text]
schemaNames = (Text, Schema) -> Text
forall a b. (a, b) -> a
fst ((Text, Schema) -> Text) -> [(Text, Schema)] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Text, Schema)]
schemaDefinitions
printWarningIfUnknownWithTypeName :: Text -> [Text] -> Generator ()
printWarningIfUnknownWithTypeName Text
typeName = (Text -> Text -> Text) -> [Text] -> [Text] -> Generator ()
printWarningIfUnknown (\Text
name Text
proposedOptions -> Text
"The " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
typeName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" '" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"' does not appear in the provided OpenAPI specification. " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
proposedOptions) [Text]
schemaNames
[Text]
whiteListedSchemas <- (Settings -> [Text]) -> Generator [Text]
forall a. (Settings -> a) -> Generator a
OAM.getSetting Settings -> [Text]
OAO.settingWhiteListedSchemas
[Text]
opaqueSchemas <- (Settings -> [Text]) -> Generator [Text]
forall a. (Settings -> a) -> Generator a
OAM.getSetting Settings -> [Text]
OAO.settingOpaqueSchemas
Text -> [Text] -> Generator ()
printWarningIfUnknownWithTypeName Text
"white-listed schema" [Text]
whiteListedSchemas
Text -> [Text] -> Generator ()
printWarningIfUnknownWithTypeName Text
"schema listed as opaque" [Text]
opaqueSchemas
printWarningIfUnknown :: (Text -> Text -> Text) -> [Text] -> [Text] -> OAM.Generator ()
printWarningIfUnknown :: (Text -> Text -> Text) -> [Text] -> [Text] -> Generator ()
printWarningIfUnknown Text -> Text -> Text
generateMessage [Text]
namesFromSpecification =
(Text -> Generator ()) -> [Text] -> Generator ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
( \Text
name ->
Bool -> Generator () -> Generator ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text
name Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
namesFromSpecification) (Generator () -> Generator ()) -> Generator () -> Generator ()
forall a b. (a -> b) -> a -> b
$
Text -> Generator ()
OAM.logWarning (Text -> Generator ()) -> Text -> Generator ()
forall a b. (a -> b) -> a -> b
$
Text -> Text -> Text
generateMessage Text
name (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$
Text -> [Text] -> Text
getProposedOptionsFromNameAndAvailableSchemas Text
name [Text]
namesFromSpecification
)
getProposedOptionsFromNameAndAvailableSchemas :: Text -> [Text] -> Text
getProposedOptionsFromNameAndAvailableSchemas :: Text -> [Text] -> Text
getProposedOptionsFromNameAndAvailableSchemas Text
name = [Text] -> Text
getProposedOptions ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> [Text]
sortByLongestCommonSubstring Text
name
sortByLongestCommonSubstring :: Text -> [Text] -> [Text]
sortByLongestCommonSubstring :: Text -> [Text] -> [Text]
sortByLongestCommonSubstring Text
needle = ((Text, Int) -> Text) -> [(Text, Int)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text, Int) -> Text
forall a b. (a, b) -> a
fst ([(Text, Int)] -> [Text])
-> ([Text] -> [(Text, Int)]) -> [Text] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Text, Int) -> Int) -> [(Text, Int)] -> [(Text, Int)]
forall b a. Ord b => (a -> b) -> [a] -> [a]
L.sortOn (Text, Int) -> Int
forall a b. (a, b) -> b
snd ([(Text, Int)] -> [(Text, Int)])
-> ([Text] -> [(Text, Int)]) -> [Text] -> [(Text, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> (Text, Int)) -> [Text] -> [(Text, Int)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Text
x -> (Text
x, -(Text -> Text -> Int
longestCommonSubstringCount Text
needle Text
x)))
getProposedOptions :: [Text] -> Text
getProposedOptions :: [Text] -> Text
getProposedOptions [] = Text
"Specification does not contain any."
getProposedOptions (Text
x1 : Text
x2 : Text
x3 : Text
_ : [Text]
_) = [Text] -> Text
getProposedOptions [Text
x1, Text
x2, Text
x3]
getProposedOptions [Text]
xs =
let separator :: Text
separator = Text
"\n "
in Text
"Did you mean one of following options?" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
separator Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
separator [Text]
xs
longestCommonSubstringCount :: Text -> Text -> Int
longestCommonSubstringCount :: Text -> Text -> Int
longestCommonSubstringCount Text
x Text
y =
let getSetWithAllSubstrings :: Text -> Set Text
getSetWithAllSubstrings = [Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList ([Text] -> Set Text) -> (Text -> [Text]) -> Text -> Set Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> [Text]
T.inits (Text -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Text -> [Text]
T.tails) (Text -> [Text]) -> (Text -> Text) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.toLower
intersection :: Set Text
intersection = Set Text -> Set Text -> Set Text
forall a. Ord a => Set a -> Set a -> Set a
Set.intersection (Text -> Set Text
getSetWithAllSubstrings Text
x) (Text -> Set Text
getSetWithAllSubstrings Text
y)
in if Set Text -> Bool
forall a. Set a -> Bool
Set.null Set Text
intersection then Int
0 else Text -> Int
T.length ((Text -> Text -> Ordering) -> Set Text -> Text
forall (t :: * -> *) a.
Foldable t =>
(a -> a -> Ordering) -> t a -> a
L.maximumBy ((Text -> Int) -> Text -> Text -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
Ord.comparing Text -> Int
T.length) Set Text
intersection)