@@ -25,8 +25,8 @@ import Control.Applicative
25
25
import Control.Arrow
26
26
(second )
27
27
import Control.Lens
28
- (makeLenses , mapped , over , set , traversed , view , (%~) , (&) ,
29
- (.~) , (<>~) , (^.) , (|>) )
28
+ (makeLenses , mapped , each , over , set , to , toListOf , traversed , view ,
29
+ _1 , (%~) , (&) , (.~) , (<>~) , (^.) , (|>) )
30
30
import qualified Data.ByteString.Char8 as BSC
31
31
import Data.ByteString.Lazy.Char8
32
32
(ByteString )
@@ -59,6 +59,9 @@ import Data.String.Conversions
59
59
import Data.Text
60
60
(Text , unpack )
61
61
import GHC.Generics
62
+ (Generic , Rep , K1 (K1 ), M1 (M1 ), U1 (U1 ), V1 ,
63
+ (:*:) ((:*:) ), (:+:) (L1 , R1 ))
64
+ import qualified GHC.Generics as G
62
65
import GHC.TypeLits
63
66
import Servant.API
64
67
import Servant.API.ContentTypes
@@ -295,7 +298,7 @@ defResponse = Response
295
298
data Action = Action
296
299
{ _authInfo :: [DocAuthentication ] -- user supplied info
297
300
, _captures :: [DocCapture ] -- type collected + user supplied info
298
- , _headers :: [Text ] -- type collected
301
+ , _headers :: [HTTP. Header ] -- type collected
299
302
, _params :: [DocQueryParam ] -- type collected + user supplied info
300
303
, _fragment :: Maybe DocFragment -- type collected + user supplied info
301
304
, _notes :: [DocNote ] -- user supplied
@@ -356,12 +359,14 @@ data ShowContentTypes = AllContentTypes -- ^ For each example, show each conten
356
359
--
357
360
-- @since 0.11.1
358
361
data RenderingOptions = RenderingOptions
359
- { _requestExamples :: ! ShowContentTypes
362
+ { _requestExamples :: ! ShowContentTypes
360
363
-- ^ How many content types to display for request body examples?
361
- , _responseExamples :: ! ShowContentTypes
364
+ , _responseExamples :: ! ShowContentTypes
362
365
-- ^ How many content types to display for response body examples?
363
- , _notesHeading :: ! (Maybe String )
366
+ , _notesHeading :: ! (Maybe String )
364
367
-- ^ Optionally group all 'notes' together under a common heading.
368
+ , _renderCurlBasePath :: ! (Maybe String )
369
+ -- ^ Optionally render example curl requests under a common base path (e.g. `http://localhost:80`).
365
370
} deriving (Show )
366
371
367
372
-- | Default API generation options.
@@ -373,9 +378,10 @@ data RenderingOptions = RenderingOptions
373
378
-- @since 0.11.1
374
379
defRenderingOptions :: RenderingOptions
375
380
defRenderingOptions = RenderingOptions
376
- { _requestExamples = AllContentTypes
377
- , _responseExamples = AllContentTypes
378
- , _notesHeading = Nothing
381
+ { _requestExamples = AllContentTypes
382
+ , _responseExamples = AllContentTypes
383
+ , _notesHeading = Nothing
384
+ , _renderCurlBasePath = Nothing
379
385
}
380
386
381
387
-- gimme some lenses
@@ -412,7 +418,7 @@ docsWithOptions p = docsFor p (defEndpoint, defAction)
412
418
-- > extra :: ExtraInfo TestApi
413
419
-- > extra =
414
420
-- > extraInfo (Proxy :: Proxy ("greet" :> Capture "greetid" Text :> Delete)) $
415
- -- > defAction & headers <>~ ["unicorns" ]
421
+ -- > defAction & headers <>~ [("X-Num-Unicorns", 1) ]
416
422
-- > & notes <>~ [ DocNote "Title" ["This is some text"]
417
423
-- > , DocNote "Second section" ["And some more"]
418
424
-- > ]
@@ -507,7 +513,7 @@ samples = map ("",)
507
513
508
514
-- | Default sample Generic-based inputs/outputs.
509
515
defaultSamples :: forall a . (Generic a , GToSample (Rep a )) => Proxy a -> [(Text , a )]
510
- defaultSamples _ = second to <$> gtoSamples (Proxy :: Proxy (Rep a ))
516
+ defaultSamples _ = second G. to <$> gtoSamples (Proxy :: Proxy (Rep a ))
511
517
512
518
-- | @'ToSample'@ for Generics.
513
519
--
@@ -643,7 +649,7 @@ markdown = markdownWith defRenderingOptions
643
649
--
644
650
-- @since 0.11.1
645
651
markdownWith :: RenderingOptions -> API -> String
646
- markdownWith RenderingOptions {.. } api = unlines $
652
+ markdownWith RenderingOptions {.. } api = unlines $
647
653
introsStr (api ^. apiIntros)
648
654
++ (concatMap (uncurry printEndpoint) . sort . HM. toList $ api ^. apiEndpoints)
649
655
@@ -654,11 +660,12 @@ markdownWith RenderingOptions{..} api = unlines $
654
660
notesStr (action ^. notes) ++
655
661
authStr (action ^. authInfo) ++
656
662
capturesStr (action ^. captures) ++
657
- headersStr (action ^. headers ) ++
663
+ headersStr (toListOf (headers . each . _1 . to ( T. pack . BSC. unpack . CI. original)) action ) ++
658
664
paramsStr meth (action ^. params) ++
659
665
fragmentStr (action ^. fragment) ++
660
666
rqbodyStr (action ^. rqtypes) (action ^. rqbody) ++
661
667
responseStr (action ^. response) ++
668
+ maybe [] (curlStr endpoint (action ^. headers) (action ^. rqbody)) _renderCurlBasePath ++
662
669
[]
663
670
664
671
where str = " ## " ++ BSC. unpack meth
@@ -814,7 +821,6 @@ markdownWith RenderingOptions{..} api = unlines $
814
821
(" text" , " css" ) -> " css"
815
822
(_, _) -> " "
816
823
817
-
818
824
contentStr mime_type body =
819
825
" " :
820
826
" ```" <> markdownForType mime_type :
@@ -839,6 +845,36 @@ markdownWith RenderingOptions{..} api = unlines $
839
845
xs ->
840
846
formatBodies _responseExamples xs
841
847
848
+ curlStr :: Endpoint -> [HTTP. Header ] -> [(Text , M. MediaType , ByteString )] -> String -> [String ]
849
+ curlStr endpoint hdrs reqBodies basePath =
850
+ [ " ### Sample Request:"
851
+ , " "
852
+ , " ```bash"
853
+ , " curl -X" ++ BSC. unpack (endpoint ^. method) ++ " \\ "
854
+ ] <>
855
+ maybe [] pure mbMediaTypeStr <>
856
+ headersStrs <>
857
+ maybe [] pure mbReqBodyStr <>
858
+ [ " " ++ basePath ++ showPath (endpoint ^. path)
859
+ , " ```"
860
+ , " "
861
+ ]
862
+
863
+ where escapeQuotes :: String -> String
864
+ escapeQuotes = concatMap $ \ c -> case c of
865
+ ' \" ' -> " \\\" "
866
+ _ -> [c]
867
+ mbReqBody = listToMaybe reqBodies
868
+ mbMediaTypeStr = mkMediaTypeStr <$> mbReqBody
869
+ headersStrs = mkHeaderStr <$> hdrs
870
+ mbReqBodyStr = mkReqBodyStr <$> mbReqBody
871
+ mkMediaTypeStr (_, media_type, _) =
872
+ " -H \" Content-Type: " ++ show media_type ++ " \" \\ "
873
+ mkHeaderStr (hdrName, hdrVal) =
874
+ " -H \" " ++ escapeQuotes (cs (CI. original hdrName)) ++ " : " ++
875
+ escapeQuotes (cs hdrVal) ++ " \" \\ "
876
+ mkReqBodyStr (_, _, body) = " -d \" " ++ escapeQuotes (cs body) ++ " \" \\ "
877
+
842
878
-- * Instances
843
879
844
880
-- | The generated docs for @a ':<|>' b@ just appends the docs
@@ -977,14 +1013,17 @@ instance {-# OVERLAPPING #-}
977
1013
status = fromInteger $ natVal (Proxy :: Proxy status )
978
1014
p = Proxy :: Proxy a
979
1015
980
- instance (KnownSymbol sym , HasDocs api )
1016
+ instance (ToHttpApiData a , ToSample a , KnownSymbol sym , HasDocs api )
981
1017
=> HasDocs (Header' mods sym a :> api ) where
982
1018
docsFor Proxy (endpoint, action) =
983
1019
docsFor subApiP (endpoint, action')
984
1020
985
1021
where subApiP = Proxy :: Proxy api
986
- action' = over headers (|> headername) action
987
- headername = T. pack $ symbolVal (Proxy :: Proxy sym )
1022
+ action' = over headers (|> (headerName, headerVal)) action
1023
+ headerName = CI. mk . cs $ symbolVal (Proxy :: Proxy sym )
1024
+ headerVal = case toSample (Proxy :: Proxy a ) of
1025
+ Just x -> cs $ toHeader x
1026
+ Nothing -> " <no header sample provided>"
988
1027
989
1028
instance (KnownSymbol sym , ToParam (QueryParam' mods sym a ), HasDocs api )
990
1029
=> HasDocs (QueryParam' mods sym a :> api ) where
0 commit comments