Skip to content

Commit

Permalink
CodeGen: Inline param refs
Browse files Browse the repository at this point in the history
  • Loading branch information
ysangkok committed Apr 11, 2024
1 parent 4f0603c commit 11bd581
Showing 1 changed file with 44 additions and 32 deletions.
76 changes: 44 additions & 32 deletions json-fleece-openapi3/src/Fleece/OpenApi3.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Fleece.OpenApi3
( generateOpenApiFleeceCode
Expand Down Expand Up @@ -50,12 +51,13 @@ unionsErrorOnConflict maps =

mkCodeGenTypes :: OA.OpenApi -> CGU.CodeGen CGU.CodeGenMap
mkCodeGenTypes openApi = do
let
components = OA._openApiComponents $ openApi

schemaMaps <-
traverse (uncurry (mkSchemaMap CGU.Type))
. IOHM.toList
. OA._componentsSchemas
. OA._openApiComponents
$ openApi
$ OA._componentsSchemas components

schemaMap <- unionsErrorOnConflict schemaMaps

Expand All @@ -68,11 +70,11 @@ mkCodeGenTypes openApi = do
codeGenMap =
fmap (CGU.CodeGenItemType . schemaCodeGenType) schemaMap

pathTypes <- traverse (uncurry $ mkPathItem schemaMap) pathItems
pathTypes <- traverse (uncurry $ mkPathItem (OA._componentsParameters components) schemaMap) pathItems
unionsErrorOnConflict (codeGenMap : pathTypes)

mkPathItem :: SchemaMap -> FilePath -> OA.PathItem -> CGU.CodeGen CGU.CodeGenMap
mkPathItem schemaMap filePath pathItem = do
mkPathItem :: OA.Definitions OA.Param -> SchemaMap -> FilePath -> OA.PathItem -> CGU.CodeGen CGU.CodeGenMap
mkPathItem paramDefs schemaMap filePath pathItem = do
let
methodOperations =
pathItemOperations pathItem
Expand All @@ -84,7 +86,7 @@ mkPathItem schemaMap filePath pathItem = do

operationCodeGenMaps <-
traverse
(uncurry $ mkOperation schemaMap filePath pathItem nameStrategy)
(uncurry $ mkOperation paramDefs schemaMap filePath pathItem nameStrategy)
methodOperations

unionsErrorOnConflict operationCodeGenMaps
Expand Down Expand Up @@ -113,15 +115,31 @@ data FallbackOperationNamingStrategy
= FallbackOperationNameIncludeMethod
| FallbackOperationNameOmitMethod

codeGenParamToRef :: CGU.CodeGenOperationParam -> CGU.OperationPathPiece
codeGenParamToRef codeGenParam =
CGU.PathParamRef
(CGU.codeGenOperationParamName codeGenParam)
(CGU.codeGenOperationParamTypeName codeGenParam)
(CGU.codeGenOperationParamDefName codeGenParam)

lookupParamRef :: T.Text -> Map.Map T.Text CGU.CodeGenOperationParam -> CGU.CodeGen CGU.CodeGenOperationParam
lookupParamRef name params =
case Map.lookup name params of
Just codeGenParam ->
pure codeGenParam
Nothing ->
CGU.codeGenError "Parameter definition not found"

mkOperation ::
OA.Definitions OA.Param ->
SchemaMap ->
FilePath ->
OA.PathItem ->
FallbackOperationNamingStrategy ->
T.Text ->
OA.Operation ->
CGU.CodeGen CGU.CodeGenMap
mkOperation schemaMap filePath pathItem nameStrategy method operation = do
mkOperation paramDefs schemaMap filePath pathItem nameStrategy method operation = do
let
pathTextParts =
filter (not . T.null)
Expand All @@ -142,29 +160,12 @@ mkOperation schemaMap filePath pathItem nameStrategy method operation = do
FallbackOperationNameIncludeMethod -> pathKey <> "." <> method

params <-
mkOperationParams schemaMap operationKey pathItem operation
mkOperationParams paramDefs schemaMap operationKey pathItem operation

let
lookupParamRef name =
case Map.lookup name params of
Just codeGenParam ->
pure $
CGU.PathParamRef
(CGU.codeGenOperationParamName codeGenParam)
(CGU.codeGenOperationParamTypeName codeGenParam)
(CGU.codeGenOperationParamDefName codeGenParam)
Nothing ->
CGU.codeGenError $
"Parameter definition not found for "
<> show name
<> " param of "
<> show method
<> " operation for "
<> filePath

mkPiece text =
if "{" `T.isPrefixOf` text && "}" `T.isSuffixOf` text
then lookupParamRef (T.drop 1 . T.dropEnd 1 $ text)
then codeGenParamToRef <$> lookupParamRef (T.drop 1 . T.dropEnd 1 $ text) params
else pure (CGU.PathLiteral text)

pathPieces <- traverse mkPiece pathTextParts
Expand Down Expand Up @@ -587,15 +588,16 @@ mkInlineOneOfSchema raiseError schemaKey schemaMap schema =
Nothing -> raiseError "Inline schema doesn't have a type."

mkOperationParams ::
OA.Definitions OA.Param ->
SchemaMap ->
T.Text ->
OA.PathItem ->
OA.Operation ->
CGU.CodeGen (Map.Map T.Text CGU.CodeGenOperationParam)
mkOperationParams schemaMap operationKey pathItem operation = do
mkOperationParams paramDefs schemaMap operationKey pathItem operation = do
paramList <-
traverse
(mkOperationParam schemaMap operationKey)
(mkOperationParam paramDefs schemaMap operationKey)
(OA._pathItemParameters pathItem <> OA._operationParameters operation)

let
Expand All @@ -607,14 +609,24 @@ mkOperationParams schemaMap operationKey pathItem operation = do
pure paramMap

mkOperationParam ::
OA.Definitions OA.Param ->
SchemaMap ->
T.Text ->
OA.Referenced OA.Param ->
CGU.CodeGen CGU.CodeGenOperationParam
mkOperationParam schemaMap operationKey paramRef = do
param <-
mkOperationParam paramDefs schemaMap operationKey paramRef = do
param :: OA.Param <-
case paramRef of
OA.Ref _ -> CGU.codeGenError "Param refs not yet implemeted."
OA.Ref name -> do
let txtName = OA.getReference name
case IOHM.lookup txtName paramDefs of
Nothing ->
CGU.codeGenError $
"Couldn't not find param def '"
<> T.unpack txtName
<> "', keys are: "
<> show (IOHM.keys paramDefs)
Just x -> pure x
OA.Inline param -> pure param

let
Expand Down

0 comments on commit 11bd581

Please sign in to comment.