]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Public.hs
Merge branch '106-dev-ngrams-score-fix' of ssh://gitlab.iscpif.fr:20022/gargantext...
[gargantext.git] / src / Gargantext / API / Public.hs
1 {-|
2 Module : Gargantext.API.Public
3 Description :
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 -}
11
12 {-# LANGUAGE TypeOperators #-}
13 {-# LANGUAGE ScopedTypeVariables #-}
14
15 module Gargantext.API.Public
16 where
17
18 import Data.Set (Set)
19 import Control.Lens ((^?), (^.), _Just)
20 import Data.Maybe (catMaybes)
21 import Data.Text (Text)
22 import Data.List (replicate, null)
23 import Data.Aeson
24 import Data.Swagger hiding (title, url)
25 import GHC.Generics (Generic)
26 import Servant
27 import Test.QuickCheck (elements)
28 import Test.QuickCheck.Arbitrary
29
30 import qualified Data.List as List
31 import qualified Data.Map as Map
32 import qualified Data.Set as Set
33
34 import Gargantext.API.Prelude
35 import Gargantext.API.Node.File
36 import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..))
37 import Gargantext.Database.Prelude
38 import Gargantext.Database.Admin.Types.Hyperdata
39 import Gargantext.Database.Admin.Types.Hyperdata.CorpusField
40 import Gargantext.Database.Admin.Types.Node
41 import Gargantext.Database.Query.Table.NodeNode (selectPublicNodes)
42 import Gargantext.Core.Utils.DateUtils (utc2year)
43 import Gargantext.Database.Schema.Node -- (NodePoly(..))
44 import Gargantext.Prelude
45 import qualified Gargantext.Utils.Aeson as GUA
46
47 ------------------------------------------------------------------------
48 type API = API_Home
49 :<|> API_Node
50
51 api :: Text -> GargServer API
52 api baseUrl = (api_home baseUrl)
53 :<|> api_node
54
55 -------------------------------------------------------------------------
56 type API_Home = Summary " Public Home API"
57 :> Get '[JSON] [PublicData]
58
59 api_home :: Text -> GargServer API_Home
60 api_home baseUrl = catMaybes
61 <$> map (toPublicData baseUrl)
62 <$> filterPublicDatas
63 <$> selectPublic
64
65 -------------------------------------------------------------------------
66 type API_Node = Summary " Public Node API"
67 :> Capture "node" NodeId
68 :> "file" :> FileApi
69
70 api_node :: NodeId -> GargServer FileApi
71 api_node nId = do
72 pubNodes <- publicNodes
73 -- TODO optimize with SQL
74 case Set.member nId pubNodes of
75 False -> panic "Not allowed" -- TODO throwErr
76 True -> fileApi 0 nId
77
78 -------------------------------------------------------------------------
79
80
81 selectPublic :: HasNodeError err
82 => Cmd err [( Node HyperdataFolder, Maybe Int)]
83 selectPublic = selectPublicNodes
84
85 -- For tests only
86 -- pure $ replicate 6 defaultPublicData
87
88 filterPublicDatas :: [(Node HyperdataFolder, Maybe Int)]
89 -> [(Node HyperdataFolder, [NodeId])]
90 filterPublicDatas datas =
91 map (\(n,mi) ->
92 let mi' = NodeId <$> mi in
93 ( _node_id n, (n, maybe [] (:[]) mi' ))
94 ) datas
95 & Map.fromListWith (\(n1,i1) (_n2,i2) -> (n1, i1 <> i2))
96 & Map.filter (not . null . snd)
97 & Map.elems
98
99 publicNodes :: HasNodeError err
100 => Cmd err (Set NodeId)
101 publicNodes = do
102 candidates <- filterPublicDatas <$> selectPublicNodes
103 pure $ Set.fromList
104 $ List.concat
105 $ map (\(n, ns) -> (_node_id n) : ns) candidates
106
107
108 -- http://localhost:8008/api/v1.0/node/23543/file/download<Paste>
109 -- http://localhost:8000/images/Gargantextuel-212x300.jpg
110 toPublicData :: Text -> (Node HyperdataFolder, [NodeId]) -> Maybe PublicData
111 toPublicData base (n , mn) = do
112 title <- (hd ^? (_Just . hf_data . cf_title))
113 abstract <- (hd ^? (_Just . hf_data . cf_desc ))
114 img <- (Just $ url' mn) -- "images/Gargantextuel-212x300.jpg"
115 url <- (Just $ url' mn)
116 date <- Just (cs $ show $ utc2year (n^.node_date))
117 database <- (hd ^? (_Just . hf_data . cf_query))
118 author <- (hd ^? (_Just . hf_data . cf_authors))
119 pure $ PublicData { .. }
120 where
121 hd = head
122 $ filter (\(HyperdataField cd _ _) -> cd == JSON)
123 $ n^. (node_hyperdata . hc_fields)
124 url' :: [NodeId] -> Text
125 url' mn' = base
126 <> "/public/"
127 <> (cs $ show $ (maybe 0 unNodeId $ head mn'))
128 <> "/file/download"
129
130
131 data PublicData = PublicData
132 { title :: Text
133 , abstract :: Text
134 , img :: Text
135 , url :: Text
136 , date :: Text
137 , database :: Text
138 , author :: Text
139 } | NoData { nodata:: Text}
140 deriving (Generic)
141
142
143 instance FromJSON PublicData where
144 parseJSON = genericParseJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
145
146 instance ToJSON PublicData where
147 toJSON = genericToJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
148
149 instance ToSchema PublicData
150 instance Arbitrary PublicData where
151 arbitrary = elements
152 $ replicate 6 defaultPublicData
153
154 defaultPublicData :: PublicData
155 defaultPublicData =
156 PublicData { title = "Title"
157 , abstract = foldl (<>) "" $ replicate 100 "abstract "
158 , img = "images/Gargantextuel-212x300.jpg"
159 , url = "https://.."
160 , date = "YY/MM/DD"
161 , database = "database"
162 , author = "Author" }
163
164
165
166