{-|
Module      : Gargantext.Core.Utils.Swagger
Description : Swagger utilities
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX

-}

---------------------------------------------------------------------
module Gargantext.Core.Utils.Swagger where
---------------------------------------------------------------------
import Control.Lens ((?~))
import Data.Swagger
import Data.Swagger qualified as S
import Data.Swagger.Declare qualified as S
import Data.Swagger.Internal.Schema qualified as S
import Data.Swagger.Internal.TypeShape qualified as S
import Data.Text qualified as T
import Gargantext.Core.Utils ((?!))
import Gargantext.Prelude
import Prelude qualified


wellNamedSchema ::
     forall a.
     ( Typeable a -- for the real full name
     , Generic a
     , S.GToSchema (Rep a)
     , S.GenericHasSimpleShape a "genericDeclareNamedSchemaUnrestricted" (S.GenericShape (Rep a))
     )
  => Text
  -> Proxy a
  -> S.Declare (S.Definitions S.Schema) S.NamedSchema
wellNamedSchema pref proxy =
  (S.name ?~ (T.replace " " "_" . T.pack . show . typeRep) proxy) <$>
  S.genericDeclareNamedSchema (swaggerOptions pref) proxy

swaggerOptions :: Text -> SchemaOptions
swaggerOptions pref = defaultSchemaOptions
  { S.fieldLabelModifier = modifier pref
  , S.unwrapUnaryRecords = False
  }

modifier :: Text -> Prelude.String -> Prelude.String
modifier pref field = T.unpack $ T.stripPrefix pref (T.pack field) ?! "Expecting prefix " <> T.unpack pref