Commit df7374f0 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[UserPage][Database] Authors to docs view.

parent 77283dfc
This diff is collapsed.
......@@ -25,9 +25,9 @@ module Gargantext.Database.Ngrams where
import Database.PostgreSQL.Simple as DPS (Connection)
--import Control.Lens.TH (makeLensesWith, abbreviatedFields)
--import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
--import Opaleye
import Control.Lens.TH (makeLensesWith, abbreviatedFields)
import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import Opaleye
import Control.Lens (makeLenses, view)
import Data.ByteString.Internal (ByteString)
import Data.Map (Map, fromList, lookup, fromListWith)
......@@ -51,38 +51,44 @@ import Prelude (Enum, Bounded, minBound, maxBound)
import qualified Data.Set as DS
import qualified Database.PostgreSQL.Simple as DPS
{-
data NgramPoly id terms n = NgramDb { ngram_id :: id
, ngram_terms :: terms
, ngram_n :: n
--{-
data NgramsPoly id terms n = NgramsDb { ngrams_id :: id
, ngrams_terms :: terms
, ngrams_n :: n
} deriving (Show)
type NgramWrite = NgramPoly (Maybe (Column PGInt4))
--}
type NgramsWrite = NgramsPoly (Maybe (Column PGInt4))
(Column PGText)
(Column PGInt4)
type NgramRead = NgramPoly (Column PGInt4)
(Column PGText)
(Column PGInt4)
type NgramsRead = NgramsPoly (Column PGInt4)
(Column PGText)
(Column PGInt4)
type NgramsReadNull = NgramsPoly (Column (Nullable PGInt4))
(Column (Nullable PGText))
(Column (Nullable PGInt4))
--type Ngram = NgramPoly Int Text Int
--{-
type NgramsDb = NgramsPoly Int Text Int
$(makeAdaptorAndInstance "pNgram" ''NgramPoly)
$(makeLensesWith abbreviatedFields ''NgramPoly)
$(makeAdaptorAndInstance "pNgramsDb" ''NgramsPoly)
-- $(makeLensesWith abbreviatedFields ''NgramsPoly)
ngramTable :: Table NgramWrite NgramRead
ngramTable = Table "ngrams" (pNgram NgramDb { ngram_id = optional "id"
, ngram_terms = required "terms"
, ngram_n = required "n"
ngramsTable :: Table NgramsWrite NgramsRead
ngramsTable = Table "ngrams" (pNgramsDb NgramsDb { ngrams_id = optional "id"
, ngrams_terms = required "terms"
, ngrams_n = required "n"
}
)
--{-
queryNgramsTable :: Query NgramsRead
queryNgramsTable = queryTable ngramsTable
queryNgramTable :: Query NgramRead
queryNgramTable = queryTable ngramTable
dbGetNgrams :: DPS.Connection -> IO [NgramDb]
dbGetNgrams conn = runQuery conn queryNgramTable
-}
dbGetNgramsDb :: DPS.Connection -> IO [NgramsDb]
dbGetNgramsDb conn = runQuery conn queryNgramsTable
--}
-- | Main Ngrams Types
-- | Typed Ngrams
......
......@@ -65,6 +65,14 @@ type NodeNgramRead =
(Column PGFloat8)
(Column PGInt4 )
type NodeNgramReadNull =
NodeNgramPoly
(Column (Nullable PGInt4 ))
(Column (Nullable PGInt4 ))
(Column (Nullable PGInt4 ))
(Column (Nullable PGFloat8))
(Column (Nullable PGInt4 ))
type NodeNgram =
NodeNgramPoly (Maybe Int) Int Int Double Int
......
......@@ -79,5 +79,5 @@ fromField' field mb = do
Success a -> pure a
Error _err -> returnError ConversionFailed field "cannot parse hyperdata"
-- | Opaleye leftJoin* functions
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