Skip to content

Commit

Permalink
Merge pull request #6 from pellagic-puffbomb/return_info_experimental
Browse files Browse the repository at this point in the history
Add more typed information to docstrings
  • Loading branch information
erewok authored Mar 8, 2017
2 parents 69e82d1 + bb915fc commit e751e16
Show file tree
Hide file tree
Showing 6 changed files with 265 additions and 81 deletions.
35 changes: 29 additions & 6 deletions examples/Main.hs
Original file line number Diff line number Diff line change
@@ -1,32 +1,53 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}

module Main where

import Data.Aeson
import qualified Data.ByteString.Char8 as B
import Data.Proxy
import Data.Data
import qualified Data.Text as T
import GHC.Generics
import Servant
import Servant.Foreign
import System.FilePath

import Servant.PY
import Servant.PY.Python

-- * A simple Counter data type
newtype Counter = Counter { value :: Int }
deriving (Generic, Show, Num)
deriving (Generic, Show, Num, Data, Typeable)
instance ToJSON Counter
-- instance HasForeignType Python T.Text Counter where
-- typeFor _ _ _ = "{\"value\": int}"

data LoginForm = LoginForm
{ username :: !T.Text
, password :: !T.Text
{ username :: !T.Text
, password :: !T.Text
, otherMissing :: Maybe T.Text
} deriving (Eq, Show, Generic)
} deriving (Eq, Show, Generic, Typeable, Data)
instance ToJSON LoginForm

-- You could provide a direct instance of your types to represent them as strings
-- instance HasForeignType Python T.Text LoginForm where
-- typeFor _ _ _ = "{\"username\": str, \"password\": str, \"otherMissing\": Maybe Text}"


-- Alternately, if you make your instance derive Typeable and Data, and
-- you enable the pragma DeriveDataTypeable,
-- then you can use recordToDict to automatically derive your records
instance HasForeignType Python T.Text LoginForm where
typeFor _ _ _ = recordToDict (undefined :: LoginForm) LoginForm

instance HasForeignType Python T.Text Counter where
typeFor _ _ _ = recordToDict (undefined :: Counter) Counter

-- * Our API type
type TestApi = "counter-req-header" :> Post '[JSON] Counter
:<|> "counter-queryparam"
Expand All @@ -51,4 +72,6 @@ result :: FilePath
result = "examples"

main :: IO ()
main = writePythonForAPI testApi requests (result </> "api.py")
main = do
writePythonForAPI testApi requests (result </> "api.py")
writeTypedPythonForAPI testApi requests (result </> "api_typed.py")
3 changes: 3 additions & 0 deletions servant-py.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -26,8 +26,10 @@ library
exposed-modules: Servant.PY
, Servant.PY.Requests
, Servant.PY.Internal
, Servant.PY.Python
build-depends: base >= 4.7 && < 5
, aeson
, bytestring
, charset
, lens
, servant-foreign
Expand Down Expand Up @@ -55,6 +57,7 @@ executable servant-py-exe
, aeson
, wai
, servant
, servant-foreign
, servant-server
, servant-blaze
, text
Expand Down
42 changes: 34 additions & 8 deletions src/Servant/PY.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,38 +4,40 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeOperators #-}

module Servant.PY ( -- * Generating javascript code from an API type
pyForAPI
module Servant.PY ( -- * Generating python code from an API type
PythonGenerator
, python
, pythonTyped
, writePythonForAPI
, PythonGenerator

, pyForAPI
, pyTypedForAPI
, writeTypedPythonForAPI
, -- * Options common to all generators
CommonGeneratorOptions(..)
, defCommonGeneratorOptions

-- Requests library
, requests


, -- * Function renamers
concatCase
, snakeCase
, camelCase

, -- * Misc.
listFromAPI
, python
, NoTypes
, GenerateList(..)
, FunctionName(..)
) where

import Data.Proxy
import Data.Proxy
import Data.Text (Text)
import qualified Data.Text as T
import Servant.Foreign

import Servant.PY.Internal
import Servant.PY.Python
import Servant.PY.Requests

-- | Generate the data necessary to generate Python code
Expand All @@ -44,14 +46,20 @@ import Servant.PY.Requests
python :: HasForeign NoTypes NoContent api => Proxy api -> Foreign NoContent api
python p = foreignFor (Proxy :: Proxy NoTypes) (Proxy :: Proxy NoContent) p defReq

-- | Generate the data necessary to generate Python code
-- for all the endpoints of an API, but try to get as much type-information
-- into Python docstrings, in order to aid discoverability of client functions.
pythonTyped :: HasForeign Python Text api => Proxy api -> Foreign Text api
pythonTyped p = foreignFor (Proxy :: Proxy Python) (Proxy :: Proxy Text) p defReq

-- | Directly generate all the Python functions for your API
-- from a 'Proxy' for your API type. You can then write it to
-- a file or integrate it in a page, for example.
pyForAPI :: (HasForeign NoTypes NoContent api, GenerateList NoContent (Foreign NoContent api))
=> 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 @@ -62,3 +70,21 @@ writePythonForAPI :: (HasForeign NoTypes NoContent api, GenerateList NoContent (
-> FilePath -- ^ path to the file you want to write the resulting javascript code into
-> IO ()
writePythonForAPI p gen fp = writeFile fp (T.unpack $ pyForAPI p gen)


-- | Directly generate all the Python functions for your API
-- from a 'Proxy' for your API type. You can then write it to
-- 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
-> 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 (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
-> 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)
Loading

0 comments on commit e751e16

Please sign in to comment.