2 Module : Gargantext.Core
3 Description : Supported Natural language
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# LANGUAGE DeriveAnyClass #-}
14 module Gargantext.Core
18 import Data.Either(Either(Left))
19 import Data.Hashable (Hashable)
20 import Data.Morpheus.Types (GQLType)
22 import Data.Text (Text, pack)
23 import Data.Tuple.Extra (swap)
24 import GHC.Generics (Generic)
25 import Gargantext.Prelude
27 import Test.QuickCheck
28 import qualified Data.Map as Map
30 ------------------------------------------------------------------------
31 -- | Language of a Text
32 -- For simplicity, we suppose text has an homogenous language
42 -- ... add your language and help us to implement it (:
44 -- | All languages supported
45 -- NOTE: Use international country codes
46 -- https://en.wikipedia.org/wiki/List_of_ISO_3166_country_codes
59 deriving (Show, Eq, Ord, Enum, Bounded, Generic, GQLType)
62 instance FromJSON Lang
63 instance ToSchema Lang where
64 declareNamedSchema = genericDeclareNamedSchemaUnrestricted defaultSchemaOptions
65 instance FromHttpApiData Lang
67 parseUrlPiece "All" = pure All
68 parseUrlPiece "DE" = pure DE
69 parseUrlPiece "EL" = pure EL
70 parseUrlPiece "EN" = pure EN
71 parseUrlPiece "ES" = pure ES
72 parseUrlPiece "FR" = pure FR
73 parseUrlPiece "IT" = pure IT
74 parseUrlPiece "PL" = pure PL
75 parseUrlPiece "PT" = pure PT
76 parseUrlPiece "RU" = pure RU
77 parseUrlPiece "UK" = pure UK
78 parseUrlPiece "ZH" = pure ZH
79 parseUrlPiece _ = Left "Unexpected value of Lang"
80 instance ToHttpApiData Lang where
81 toUrlPiece = pack . show
82 instance Hashable Lang
84 instance Arbitrary Lang where
85 arbitrary = arbitraryBoundedEnum
88 allLangs = [minBound .. maxBound]
94 -- NOTE: We try to use numeric codes for countries
95 -- https://en.wikipedia.org/wiki/List_of_ISO_3166_country_codes
96 -- https://en.wikipedia.org/wiki/ISO_3166-1_numeric#004
97 dbIds :: [(Lang, Int)]
112 instance HasDBid Lang where
113 toDBid lang = case Map.lookup lang $ Map.fromList dbIds of
115 Nothing -> panic "[G.Core] Add this lang to DB ids"
117 fromDBid dbId = case Map.lookup dbId $ Map.fromList $ map swap dbIds of
119 Nothing -> panic "HasDBid lang, not implemented"
121 ------------------------------------------------------------------------
122 data NLPServerConfig = NLPServerConfig
123 { server :: !PosTagAlgo
125 deriving (Show, Eq, Generic)
126 ------------------------------------------------------------------------
129 ------------------------------------------------------------------------
130 data PosTagAlgo = CoreNLP | JohnSnowServer | Spacy
131 deriving (Show, Read, Eq, Ord, Generic, GQLType)
133 instance Hashable PosTagAlgo
135 instance HasDBid PosTagAlgo where
137 toDBid JohnSnowServer = 2
140 fromDBid 2 = JohnSnowServer
142 fromDBid _ = panic "HasDBid posTagAlgo : Not implemented"