]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Node/Corpus/Types.hs
Revert b3fb1a1697d18777af6b401c132c39a5c905e129
[gargantext.git] / src / Gargantext / API / Node / Corpus / Types.hs
1 {-# LANGUAGE TemplateHaskell #-}
2
3 module Gargantext.API.Node.Corpus.Types where
4
5 import Control.Lens hiding (elements, Empty)
6 import Control.Monad.Fail (fail)
7 import Control.Monad.Reader (MonadReader)
8 import Data.Aeson
9 import Data.Aeson.TH (deriveJSON)
10 import Data.Monoid (mempty)
11 import Data.Swagger
12 import GHC.Generics (Generic)
13 import Test.QuickCheck
14 import qualified Data.Text as T
15 import qualified PUBMED.Types as PUBMED
16
17 import Gargantext.Prelude
18
19 import qualified Gargantext.API.Admin.Orchestrator.Types as Types
20 import Gargantext.Core.Utils.Prefix (unPrefix)
21 import Gargantext.Database.Action.Flow (DataOrigin(..))
22 import Gargantext.Database.Prelude (HasConfig(..))
23
24 data Database = Empty
25 | PubMed { _api_key :: Maybe PUBMED.APIKey }
26 | Arxiv
27 | HAL
28 | IsTex
29 | Isidore
30 deriving (Eq, Show, Generic)
31
32 instance Arbitrary Database
33 where
34 arbitrary = elements [ Empty
35 , PubMed { _api_key = Nothing }
36 , Arxiv
37 , HAL
38 , IsTex
39 , Isidore ]
40
41
42 deriveJSON (unPrefix "") ''Database
43 instance ToSchema Database where
44 declareNamedSchema = genericDeclareNamedSchemaUnrestricted defaultSchemaOptions
45
46 database2origin :: ( MonadReader env m
47 , HasConfig env ) => Database -> m DataOrigin
48 database2origin Empty = pure $ InternalOrigin Types.IsTex
49 database2origin (PubMed { _api_key }) = do
50 -- pubmed_api_key <- view $ hasConfig . gc_pubmed_api_key
51
52 pure $ ExternalOrigin $ Types.PubMed { mAPIKey = _api_key }
53 database2origin Arxiv = pure $ ExternalOrigin Types.Arxiv
54 database2origin HAL = pure $ ExternalOrigin Types.HAL
55 database2origin IsTex = pure $ ExternalOrigin Types.IsTex
56 database2origin Isidore = pure $ ExternalOrigin Types.Isidore
57
58 ------------------------------------------------------------------------
59 data Datafield = Gargantext
60 | External Database
61 | Web
62 | Files
63 deriving (Eq, Show, Generic)
64
65 instance FromJSON Datafield where
66 parseJSON = withText "Datafield" $ \text ->
67 case text of
68 "Gargantext"
69 -> pure Gargantext
70 "Web"
71 -> pure Web
72 "Files"
73 -> pure Files
74 v -> case T.breakOnEnd " " v of
75 ("External ", dbName)
76 -> External <$> parseJSON (String dbName)
77 _ -> fail $ "Cannot match patterh 'External <db>' for string " <> T.unpack v
78
79 instance ToJSON Datafield where
80 toJSON (External db) = toJSON $ "External " <> show db
81 toJSON s = toJSON $ show s
82
83 instance Arbitrary Datafield where
84 arbitrary = oneof [pure Gargantext, pure Web, pure Files, External <$> arbitrary]
85
86 instance ToSchema Datafield where
87 declareNamedSchema _ = do
88 return $ NamedSchema (Just "Datafield") $ mempty
89 & type_ ?~ SwaggerObject