module Servant.API.Routes.Golden
(
goldenRoutes
, goldenRoutesSpec
)
where
import Control.Monad ((>=>))
import qualified Data.Aeson as A
import qualified Data.Aeson.Encode.Pretty as P
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TLE
import qualified Data.Text.Lazy.IO as TL
import Servant.API.Routes
import qualified Test.Hspec.Core.Spec as H
import qualified Test.Hspec.Golden as G
goldenRoutes :: forall api. (HasRoutes api) => String -> G.Golden A.Value
goldenRoutes :: forall api. HasRoutes api => String -> Golden Value
goldenRoutes String
name =
(String -> String -> Golden String
G.defaultGolden String
name String
"")
{ G.output = A.toJSON . Routes $ getRoutes @api
, G.encodePretty = T.unpack . TL.toStrict . pretty
, G.writeToFile = \String
fp -> String -> LazyText -> IO ()
TL.writeFile String
fp (LazyText -> IO ()) -> (Value -> LazyText) -> Value -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> LazyText
pretty
, G.readFromFile = A.eitherDecodeFileStrict @A.Value >=> either fail pure
}
where
pretty :: Value -> LazyText
pretty = ByteString -> LazyText
TLE.decodeUtf8 (ByteString -> LazyText)
-> (Value -> ByteString) -> Value -> LazyText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> Value -> ByteString
forall a. ToJSON a => Config -> a -> ByteString
P.encodePretty' (Config
P.defConfig {P.confCompare = compare})
goldenRoutesSpec :: forall api. (HasRoutes api) => String -> H.Spec
goldenRoutesSpec :: forall api. HasRoutes api => String -> Spec
goldenRoutesSpec = String -> Golden Value -> SpecWith (Arg (Golden Value))
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
H.it String
"Generates the correct Routes" (Golden Value -> Spec)
-> (String -> Golden Value) -> String -> Spec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall api. HasRoutes api => String -> Golden Value
goldenRoutes @api