Commit 59dcfb62 authored by mzheng's avatar mzheng

small refactoring

parent d4e01a75
Pipeline #6106 passed with stages
in 176 minutes and 6 seconds
......@@ -25,14 +25,14 @@ api :: NodeId
-- ^ The ID of the target user
-> PhyloId
-> GargServer API
api userNodeId dId = getPhylo userNodeId dId
api userNodeId dId = getPhyloJson userNodeId dId
:<|> getPhyloDot userNodeId dId
getPhylo :: NodeId
-- ^ The ID of the target user
-> PhyloId
-> GargNoServer (Headers '[Header "Content-Disposition" T.Text] Value)
getPhylo _ pId = do
getPhyloJson :: NodeId
-- ^ The ID of the target user
-> PhyloId
-> GargNoServer (Headers '[Header "Content-Disposition" T.Text] Value)
getPhyloJson _ pId = do
maybePhyloData <- getPhyloData pId
let phyloData = fromMaybe phyloCleopatre maybePhyloData
phyloJson <- liftBase $ phylo2dot2json phyloData
......
......@@ -13,7 +13,7 @@ Portability : POSIX
module Gargantext.API.Node.Phylo.Export.Types where
import Data.Aeson (ToJSON, Value, encode)
import Data.Aeson
import Data.Aeson.TH (deriveJSON)
-- import Data.Csv (DefaultOrdered(..), ToNamedRecord(..), (.=), header, namedRecord)
import Data.Swagger ( genericDeclareNamedSchema, ToParamSchema(..), ToSchema(..) )
......@@ -27,7 +27,7 @@ import Gargantext.Database.Admin.Types.Node (PhyloId)
-- import Gargantext.Utils.Servant (ZIP)
-- import Gargantext.Utils.Zip (zipContentsPure)
import Protolude
import Servant ((:>), (:<|>), Get, Header, Headers(..), JSON, MimeRender(..), Summary) --, PlainText
import Servant ((:>), (:<|>), Get, Header, Headers(..), JSON, Summary) --, PlainText, MimeRender(..)
-- | Phylo Export
......@@ -36,7 +36,6 @@ data PhyloExport =
, _pe_garg_version :: Text
} deriving (Generic)
-- | This is to represent a zipped phylo export. We want to have doc_id in zipped file name.
data PhyloExportDOT =
PhyloExportDOT { _ped_dexp :: PhyloExport
, _ped_doc_id :: PhyloId
......@@ -108,27 +107,10 @@ type API = Summary "Phylo Export"
-- type API = Summary "Phylo Export"
-- :> "export"
-- :> ( "json"
-- :> Get '[JSON] (Headers '[Servant.Header "Content-Disposition" Text] Value)
-- )
-- :> Get '[JSON,DOT] (Headers '[Servant.Header "Content-Disposition" Text] Value)
data User = User
{ _us_name :: Text
, _us_age :: Int
, _us_email :: Text
} deriving (Eq, Show, Generic)
instance ToJSON User
instance ToSchema User where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_us_")
instance ToParamSchema User where
toParamSchema _ = toParamSchema (Proxy :: Proxy TODO)
instance MimeRender JSON User where
mimeRender _ = encode
$(deriveJSON (unPrefix "_p_") ''Phylo)
$(deriveJSON (unPrefix "_pe_") ''PhyloExport)
......
......@@ -54,7 +54,6 @@ import Prelude qualified
import System.FilePath ((</>))
import System.IO.Temp (withTempDirectory)
import System.Process qualified as Shell
-- import Debug.Trace qualified as DT
--------------------------------------------------------------------
getPhyloData :: HasNodeError err
......@@ -77,7 +76,8 @@ phylo2dot2json phylo = do
fileDot = dirPath </> "phylo.dot"
fileToJson = dirPath </> "output.json"
dotToFile fileFrom (toPhyloExport phylo)
phyloContent <- phylo2dot phylo
writeFile fileFrom phyloContent
-- parsing a file can be done with:
-- runParser' (Data.GraphViz.Parsing.parse :: Parse (Data.GraphViz.DotGraph Text)) $ TL.fromStrict f
......@@ -102,7 +102,7 @@ phylo2dot phylo = do
value <- readFile fileFrom
case value of
"" -> panic "[G.C.V.Phylo.API.phylo2dot2json] Error no file"
"" -> panic "[G.C.V.Phylo.API.phylo2dot] Error no file"
_ -> pure value
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment