{-|
Module      : Gargantext.API.Node.Phylo.Export
Description : Phylo export
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX
-}

module Gargantext.API.Node.Phylo.Export
  where

import Data.Aeson
import Data.Text qualified as T
import Gargantext.API.Prelude (GargNoServer, IsGargServer)
import Gargantext.API.Routes.Named.Viz qualified as Named
import Gargantext.Core.Viz.Phylo.API.Tools
import Gargantext.Core.Viz.Phylo.Example (phyloCleopatre)
import Gargantext.Database.Admin.Types.Node (PhyloId, NodeId,)
import Gargantext.Prelude
import Servant
import Servant.Server.Generic (AsServerT)

api :: IsGargServer env err m
    => NodeId
    -- ^ The ID of the target user
    -> PhyloId
    -> Named.PhyloExportAPI (AsServerT m)
api userNodeId dId = Named.PhyloExportAPI $ Named.PhyloExportEndpoints
  { exportPhyloJSONEp = getPhyloJson userNodeId dId
  , exportPhyloDotEp  = getPhyloDot userNodeId dId
  }

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
  pure $ addHeader (T.concat [ "attachment; filename="
                                          , "GarganText_Phylo-"
                                          , T.pack (show pId)
                                          , ".json" ])
                                          phyloJson


getPhyloDot :: NodeId
            -> PhyloId
            -> GargNoServer (Headers '[Header "Content-Disposition" T.Text] T.Text)
getPhyloDot _ pId = do
  maybePhyloData <- getPhyloData pId
  let phyloData = fromMaybe phyloCleopatre maybePhyloData
  phyloDot <- liftBase $ phylo2dot phyloData
  pure $ addHeader (T.concat [ "attachment; filename="
                                          , "GarganText_Phylo-"
                                          , T.pack (show pId)
                                          , ".dot" ])
                                          phyloDot