Skip to content

Commit

Permalink
Start to add some typing information to the docstrings
Browse files Browse the repository at this point in the history
  • Loading branch information
erewok committed Mar 8, 2017
1 parent 7b75790 commit bb915fc
Show file tree
Hide file tree
Showing 4 changed files with 113 additions and 103 deletions.
2 changes: 1 addition & 1 deletion examples/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,4 +74,4 @@ result = "examples"
main :: IO ()
main = do
writePythonForAPI testApi requests (result </> "api.py")
writeTypedPythonForAPI testApi requestsTyped (result </> "api_typed.py")
writeTypedPythonForAPI testApi requests (result </> "api_typed.py")
14 changes: 6 additions & 8 deletions src/Servant/PY.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,8 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeOperators #-}

module Servant.PY ( -- * Generating javascript code from an API type
module Servant.PY ( -- * Generating python code from an API type
PythonGenerator
, PythonTypedGenerator
, python
, pythonTyped
, writePythonForAPI
Expand All @@ -19,7 +18,6 @@ module Servant.PY ( -- * Generating javascript code from an API type

-- Requests library
, requests
, requestsTyped

, -- * Function renamers
concatCase
Expand All @@ -33,7 +31,7 @@ module Servant.PY ( -- * Generating javascript code from an API type
, FunctionName(..)
) where

import Data.Proxy
import Data.Proxy
import Data.Text (Text)
import qualified Data.Text as T
import Servant.Foreign
Expand Down Expand Up @@ -61,7 +59,7 @@ pyForAPI :: (HasForeign NoTypes NoContent api, GenerateList NoContent (Foreign N
=> Proxy api -- ^ proxy for your API type
-> PythonGenerator -- ^ python code generator to use (requests is the only one for now)
-> Text -- ^ a text that you can embed in your pages or write to a file
pyForAPI p gen = gen (listFromAPI (Proxy :: Proxy NoTypes) (Proxy :: Proxy NoContent) p)
pyForAPI p gen = gen (UnTypedPythonRequest <$> listFromAPI (Proxy :: Proxy NoTypes) (Proxy :: Proxy NoContent) p)

-- | Directly generate all the Python functions for your API
-- from a 'Proxy' for your API type using the given generator
Expand All @@ -79,14 +77,14 @@ writePythonForAPI p gen fp = writeFile fp (T.unpack $ pyForAPI p gen)
-- a file or integrate it in a page, for example.
pyTypedForAPI :: (HasForeign Python T.Text api, GenerateList T.Text (Foreign T.Text api))
=> Proxy api -- ^ proxy for your API type
-> PythonTypedGenerator -- ^ python code generator to use (requests is the only one for now)
-> PythonGenerator -- ^ python code generator to use (requests is the only one for now)
-> Text -- ^ a text that you can embed in your pages or write to a file
pyTypedForAPI p gen = gen (listFromAPI (Proxy :: Proxy Python) (Proxy :: Proxy T.Text) p)
pyTypedForAPI p gen = gen (TypedPythonRequest <$> listFromAPI (Proxy :: Proxy Python) (Proxy :: Proxy T.Text) p)


writeTypedPythonForAPI :: (HasForeign Python T.Text api, GenerateList T.Text (Foreign T.Text api))
=> Proxy api -- ^ proxy for your API type
-> PythonTypedGenerator -- ^ python code generator to use (requests is the only one for now)
-> PythonGenerator -- ^ python code generator to use (requests is the only one for now)
-> FilePath -- ^ path to the file you want to write the resulting javascript code into
-> IO ()
writeTypedPythonForAPI p gen fp = writeFile fp (T.unpack $ pyTypedForAPI p gen)
149 changes: 93 additions & 56 deletions src/Servant/PY/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,19 +1,15 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Servant.PY.Internal
( PythonGenerator
, ReturnStyle(..)
, InformationLevel(..)
, PythonRequest(..)
, PyRequestArgs(..)
, CommonGeneratorOptions(..)
, defCommonGeneratorOptions
, defTypedCommonGeneratorOptions
, PyRequest
, PythonTypedGenerator
, defaultPyIndent
, indent
, Indent
Expand All @@ -23,10 +19,18 @@ module Servant.PY.Internal
, segmentToStr
, capturesToFormatArgs
, toValidFunctionName
, functionName
, toPyHeader
, retrieveHeaders
, getHeaderDict
, retrieveHeaderText
, toPyDict
, toPyParams
, getParams
, paramNames
, captures
, getMethod
, hasBody
, withFormattedCaptures
, buildDocString
, buildHeaderDict
Expand Down Expand Up @@ -78,12 +82,12 @@ import Servant.Foreign


-- A 'PythonGenerator' just takes the data found in the API type
-- for each endpoint and generates Python code as Text. We have untyped and those
-- that contain typing information.
type PythonGenerator = [PyRequest NoContent] -> Text
type PythonTypedGenerator = [PyRequest Text] -> Text

type PyRequest = Req
-- for each endpoint and generates Python code as Text.
-- There are `NoContent` requests and Text requests with typing information.
type PythonGenerator = [PythonRequest] -> Text
data PythonRequest = TypedPythonRequest (Req Text)
| UnTypedPythonRequest (Req NoContent)
deriving (Eq, Show)

-- We'd like to encode at the type-level that indentation
-- is some multiplication of whitespace (sorry: never tabs!)
Expand All @@ -93,6 +97,7 @@ indent :: Proxy Indent
indent = Proxy

-- The defaultPyIndent function is 4 spaces.
-- You can create a different indentation width by passing a different Int to indenter.
defaultPyIndent :: Proxy Indent -> Text
defaultPyIndent = indenter 4

Expand All @@ -108,8 +113,11 @@ data ReturnStyle = DangerMode -- Throw caution to the wind and return JSON
| RawResponse -- Return response object itself


data InformationLevel = WithTypes -- Must use Pragma DeriveDataTypeable and do deriving (Data, Typeable)
| Minimal -- Really doesn't say much about the arguments of functions or return vals
data PyRequestArgs = PyRequestArgs {
hasHeaders :: Bool
, hasParams :: Bool
, hasData :: Bool
} deriving (Show)

-- | This structure is used by specific implementations to let you
-- customize the output
Expand All @@ -123,11 +131,9 @@ data CommonGeneratorOptions = CommonGeneratorOptions
, urlPrefix :: Text
-- ^ a prefix we should add to the Url in the codegen
, indentation :: Proxy Indent -> Text
-- ^ indentation to use for Python codeblocks
-- ^ indentation to use for Python codeblocks. Create this function by passing an Int to indenter.
, returnMode :: ReturnStyle
-- ^ whether the generated functions return the raw response or content
, informationMode :: InformationLevel
-- ^ if we should include more information on request bodies and objects returned
}

-- | Default options.
Expand All @@ -139,7 +145,6 @@ data CommonGeneratorOptions = CommonGeneratorOptions
-- > , urlPrefix = ""
-- > , indentation = " " -- 4 spaces
-- > , returnMode = DangerMode
-- > , informationMode = Minimal
-- > }
-- @
defCommonGeneratorOptions :: CommonGeneratorOptions
Expand All @@ -150,18 +155,6 @@ defCommonGeneratorOptions = CommonGeneratorOptions
, urlPrefix = "http://localhost:8000"
, indentation = defaultPyIndent
, returnMode = DangerMode
, informationMode = Minimal
}

defTypedCommonGeneratorOptions :: CommonGeneratorOptions
defTypedCommonGeneratorOptions = CommonGeneratorOptions
{
functionNameBuilder = snakeCase
, requestBody = "data"
, urlPrefix = "http://localhost:8000"
, indentation = defaultPyIndent
, returnMode = DangerMode
, informationMode = WithTypes
}

-- | Attempts to reduce the function name provided to that allowed by @'Foreign'@.
Expand Down Expand Up @@ -196,7 +189,11 @@ toValidFunctionName t =
, Set.connectorPunctuation
])

-- Javascript identifiers can only contain codepoints in the Basic Multilingual Plane
functionName :: CommonGeneratorOptions -> PythonRequest -> Text
functionName opts (TypedPythonRequest req) = toValidFunctionName (functionNameBuilder opts $ req ^. reqFuncName)
functionName opts (UnTypedPythonRequest req) = toValidFunctionName (functionNameBuilder opts $ req ^. reqFuncName)

-- Identifiers can only contain codepoints in the Basic Multilingual Plane
-- that is, codepoints that can be encoded in UTF-16 without a surrogate pair (UCS-2)
-- that is, codepoints that can fit in 16-bits, up to 0xffff (65535)
filterBmpChars :: Set.CharSet -> Set.CharSet
Expand All @@ -214,11 +211,22 @@ toPyDict offset dict

-- Query params are passed into the function that makes the request, so we make
-- a python dict out of them.
getParams :: Text -> PythonRequest -> Text
getParams offset (TypedPythonRequest req) = toPyParams offset $ req ^.. reqUrl.queryStr.traverse
getParams offset (UnTypedPythonRequest req) = toPyParams offset $ req ^.. reqUrl.queryStr.traverse

toPyParams :: Text -> [QueryArg f] -> Text
toPyParams _ [] = ""
toPyParams offset qargs = toPyDict offset paramList
where paramList = fmap (\qarg -> qarg ^. queryArgName.argName._PathSegment) qargs

-- We also need to make sure we can retrieve just the param names for function args.
paramNames :: PythonRequest -> [Text]
paramNames (TypedPythonRequest req) = map (view $ queryArgName . argPath) $ req ^.. reqUrl.queryStr.traverse
paramNames (UnTypedPythonRequest req) = map (view $ queryArgName . argPath) $ req ^.. reqUrl.queryStr.traverse

-- Request headers are also passed into the function that makes the request, so we make
-- a python dict out of them.
toPyHeader :: HeaderArg f -> Text
toPyHeader (HeaderArg n)
= toValidFunctionName ("header" <> n ^. argName . _PathSegment)
Expand All @@ -233,27 +241,30 @@ toPyHeader (ReplaceHeaderArg n p)
pn = "{" <> n ^. argName . _PathSegment <> "}"
rp = T.replace pn "" p

captures :: forall f. Req f -> [T.Text]
captures req = map (view argPath . captureArg)
. filter isCapture
$ req ^. reqUrl.path

buildHeaderDict :: [HeaderArg f] -> Text
buildHeaderDict [] = ""
buildHeaderDict hs = "{" <> headers <> "}"
where headers = T.intercalate ", " $ map headerStr hs
headerStr header = "\"" <> header ^. headerArg . argPath <> "\": "
<> toPyHeader header

getHeaderDict :: PythonRequest -> Text
getHeaderDict (TypedPythonRequest req) = buildHeaderDict $ req ^. reqHeaders
getHeaderDict (UnTypedPythonRequest req) = buildHeaderDict $ req ^. reqHeaders

retrieveHeaders :: PythonRequest -> [T.Text]
retrieveHeaders (TypedPythonRequest req) = retrieveHeaderText <$> req ^. reqHeaders
retrieveHeaders (UnTypedPythonRequest req) = retrieveHeaderText <$> req ^. reqHeaders

retrieveHeaderText :: forall f. HeaderArg f -> T.Text
retrieveHeaderText header = header ^. headerArg . argPath


functionArguments :: forall f. Req f -> T.Text
functionArguments req =
mconcat [ T.intercalate ", " args]
where
args = captures' ++ qparam ++ body ++ headers

captures' = map (view argPath . captureArg)
$ filter isCapture
$ req ^. reqUrl . path
args = captures' req ++ qparam ++ body ++ headers

qparam = map ((<>) "param_" . view (queryArgName . argPath)) queryParams

Expand All @@ -265,17 +276,31 @@ functionArguments req =
. view (headerArg . argPath)
) $ req ^. reqHeaders

captures :: PythonRequest -> [T.Text]
captures (TypedPythonRequest req) = captures' req
captures (UnTypedPythonRequest req) = captures' req

makePyUrl :: forall f. CommonGeneratorOptions -> Req f -> Text -> Text
makePyUrl opts req offset = if url' == "\"" then "\"/\"" else url'

captures' :: forall f. Req f -> [T.Text]
captures' req = map (view argPath . captureArg)
. filter isCapture
$ req ^. reqUrl.path

makePyUrl :: CommonGeneratorOptions -> PythonRequest -> Text -> Text
makePyUrl opts (TypedPythonRequest req) offset = makePyUrl' opts req offset
makePyUrl opts (UnTypedPythonRequest req) offset = makePyUrl' opts req offset

makePyUrl' :: forall f. CommonGeneratorOptions -> Req f -> Text -> Text
makePyUrl' opts req offset = if url' == "\"" then "\"/\"" else url'
where url' = "\"" <> urlPrefix opts <> "/"
<> makePyUrl' pathParts
<> getSegments pathParts
<> withFormattedCaptures offset pathParts
pathParts = req ^.. reqUrl.path.traverse

makePyUrl' :: [Segment f] -> Text
makePyUrl' [] = ""
makePyUrl' segments = T.intercalate "/" (map segmentToStr segments) <> "\""
getSegments :: forall f. [Segment f] -> T.Text
getSegments segments = if null segments
then ""
else T.intercalate "/" (map segmentToStr segments) <> "\""

withFormattedCaptures :: Text -> [Segment f] -> Text
withFormattedCaptures offset segments = formattedCaptures (capturesToFormatArgs segments)
Expand Down Expand Up @@ -303,21 +328,33 @@ captureArgsWithTypes segments = map getSegmentArgType (filter isCapture segment
getSegmentArgType _ = ""
pathPart s = s ^. argName . _PathSegment

buildDocString :: forall f. Req f -> CommonGeneratorOptions -> T.Text
buildDocString req opts = T.toUpper method <> " \"" <> url <> "\n"

buildDocString :: PythonRequest -> CommonGeneratorOptions -> T.Text
buildDocString (TypedPythonRequest req) opts = buildDocString' req opts args
where args = captureArgsWithTypes $ req ^.. reqUrl.path.traverse
buildDocString (UnTypedPythonRequest req) opts = buildDocString' req opts args
where args = capturesToFormatArgs $ req ^.. reqUrl.path.traverse

buildDocString' :: forall f. Req f -> CommonGeneratorOptions -> [T.Text] -> T.Text
buildDocString' req opts args = T.toUpper method <> " \"" <> url <> "\n"
<> includeArgs <> "\n\n"
<> indent' <> "Returns: " <> "\n"
<> indent' <> indent' <> returnVal
where method = decodeUtf8 $ req ^. reqMethod
url = makePyUrl' $ req ^.. reqUrl.path.traverse
url = getSegments $ req ^.. reqUrl.path.traverse
includeArgs = if null args then "" else argDocs
argDocs = indent' <> "Args: " <> "\n"
<> indent' <> indent' <> T.intercalate ("\n" <> indent' <> indent') args

indent' = indentation opts indent
args = case informationMode opts of
Minimal -> capturesToFormatArgs $ req ^.. reqUrl.path.traverse
WithTypes -> capturesToFormatArgs $ req ^.. reqUrl.path.traverse
returnVal = case returnMode opts of
DangerMode -> "JSON response from the endpoint"
RawResponse -> "response (requests.Response) from issuing the request"

getMethod :: PythonRequest -> Text
getMethod (TypedPythonRequest req) = decodeUtf8 $ req ^. reqMethod
getMethod (UnTypedPythonRequest req) = decodeUtf8 $ req ^. reqMethod

hasBody :: PythonRequest -> Bool
hasBody (TypedPythonRequest req) = isJust (req ^. reqBody)
hasBody (UnTypedPythonRequest req) = isJust (req ^. reqBody)
Loading

0 comments on commit bb915fc

Please sign in to comment.