Facet.hs 8.97 KB
Newer Older
1 2 3 4 5 6 7 8 9 10
{-|
Module      : Gargantext.Database.Facet
Description : Main requests of Node to the database
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX
-}

11
{-# OPTIONS_GHC -fno-warn-orphans        #-}
12
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
13

14 15 16 17 18 19 20 21 22
{-# LANGUAGE Arrows                    #-}
{-# LANGUAGE DeriveGeneric             #-}
{-# LANGUAGE FlexibleContexts          #-}
{-# LANGUAGE FlexibleInstances         #-}
{-# LANGUAGE FunctionalDependencies    #-}
{-# LANGUAGE MultiParamTypeClasses     #-}
{-# LANGUAGE NoImplicitPrelude         #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE TemplateHaskell           #-}
23

24
------------------------------------------------------------------------
25 26
module Gargantext.Database.Facet 
  where
27
------------------------------------------------------------------------
28 29

import Prelude hiding (null, id, map, sum, not)
30
import GHC.Generics (Generic)
31 32 33 34

-- import Data.Aeson (Value)
import Control.Arrow (returnA)
import Control.Lens.TH (makeLensesWith, abbreviatedFields)
35 36

import Data.Aeson.TH (deriveJSON)
37
import Data.Maybe (Maybe)
38
import Data.Profunctor.Product.Default (Default)
39 40
import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import Data.Time (UTCTime)
41
import Data.Time.Segment (jour)
42
import Data.Swagger
43

44 45 46
import           Database.PostgreSQL.Simple (Connection)
import           Opaleye
import           Opaleye.Internal.Join (NullMaker)
47
import qualified Opaleye.Internal.Unpackspec()
48 49 50 51

import Test.QuickCheck.Arbitrary
import Test.QuickCheck (elements)

52
import Gargantext.Core.Types
53
import Gargantext.Database.Types.Node (NodeType)
54
import Gargantext.Core.Utils.Prefix (unPrefix)
55 56 57 58
import Gargantext.Database.NodeNode
import Gargantext.Database.NodeNodeNgram
import Gargantext.Database.Node
import Gargantext.Database.Queries
59
import Gargantext.Database.Config (nodeTypeId)
60
-- import Gargantext.Database.NodeNgram
61

62 63
------------------------------------------------------------------------
-- | DocFacet
64 65 66 67 68 69

-- data Facet = FacetDoc | FacetSources | FacetAuthors | FacetTerms
--    deriving (Show, Generic)
--instance FromJSON Facet
--instance ToJSON   Facet

70
type FacetDoc = Facet NodeId UTCTime HyperdataDocument Bool Int
71 72 73 74 75
type FacetSources = FacetDoc
type FacetAuthors = FacetDoc
type FacetTerms   = FacetDoc


76

77
data Facet id created hyperdata favorite ngramCount = 
78
     FacetDoc { facetDoc_id         :: id
79 80 81 82 83 84
               , facetDoc_created    :: created
               , facetDoc_hyperdata  :: hyperdata
               , facetDoc_favorite   :: favorite
               , facetDoc_ngramCount :: ngramCount
               } deriving (Show, Generic)

85 86
-- | JSON instance

87 88
$(deriveJSON (unPrefix "facetDoc_") ''Facet)

89 90 91 92 93
-- | Documentation instance
instance ToSchema FacetDoc

-- | Mock and Quickcheck instances

94
instance Arbitrary FacetDoc where
95
    arbitrary = elements [ FacetDoc id' (jour year 01 01) hp fav ngramCount
96 97 98 99
                         | id'  <- [1..10]
                         , year <- [1990..2000]
                         , hp   <- hyperdataDocuments
                         , fav  <- [True, False]
100
                         , ngramCount <- [3..100]
101 102 103
                         ]

-- Facets / Views for the Front End
104 105 106 107
-- | Database instances
$(makeAdaptorAndInstance "pFacetDoc" ''Facet)
$(makeLensesWith abbreviatedFields   ''Facet)

108 109 110 111 112 113
type FacetDocRead = Facet (Column PGInt4       )
                          (Column PGTimestamptz)
                          (Column PGJsonb      )
                          (Column PGBool       )
                          (Column PGInt4       )

114 115 116 117 118 119 120 121 122 123 124 125 126
-----------------------------------------------------------------------

data FacetChart = FacetChart { facetChart_time  :: UTCTime'
                             , facetChart_count :: Double
                        }
        deriving (Show, Generic)
$(deriveJSON (unPrefix "facetChart_") ''FacetChart)
instance ToSchema FacetChart

instance Arbitrary FacetChart where
    arbitrary = FacetChart <$> arbitrary <*> arbitrary

-----------------------------------------------------------------------
127 128


129 130
getDocFacet :: Connection -> NodeType -> Int -> Maybe NodeType 
            -> Maybe Offset -> Maybe Limit
131
            -> IO [FacetDoc]
132 133
getDocFacet conn parentType parentId nodeType maybeOffset maybeLimit =
    runQuery conn $ selectDocFacet parentType parentId nodeType maybeOffset maybeLimit
134

135 136
selectDocFacet :: NodeType -> ParentId -> Maybe NodeType
               -> Maybe Offset -> Maybe Limit
137
               -> Query FacetDocRead
138 139 140 141
selectDocFacet pType parentId maybeNodeType maybeOffset maybeLimit =
        limit' maybeLimit $ offset' maybeOffset
                          $ orderBy (asc facetDoc_created)
                          $ selectDocFacet' pType parentId maybeNodeType
142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184


-- | Left join to the favorites
nodeNodeLeftJoin :: Query (NodeRead, NodeNodeReadNull)
nodeNodeLeftJoin = leftJoin queryNodeTable queryNodeNodeTable (eqNode)
    where
        eqNode (Node n1 _ _ _ _ _ _, NodeNode _ n2 _) = ((.==) n1 n2)


nodeNodeLeftJoin' :: (Column (Nullable PGInt4)) 
                  -> Query (NodeRead, NodeNodeReadNull)
nodeNodeLeftJoin' nId = leftJoin queryNodeTable queryNodeNodeTable (eqNode nId)
        where
            eqNode n (Node n1 _ _ _ _ _ _, NodeNode n1' n2 _) 
                   = foldl (.&&) (pgBool True) [ ((.==) n1 n2)
                                               , ((.==) n1' n)
                                               ]

nodeNodeLeftJoin'' :: Query (NodeRead, NodeRead, NodeNodeRead)
nodeNodeLeftJoin'' = join3 queryNodeTable queryNodeTable queryNodeNodeTable eqNode
        where
            eqNode (Node n1 _ _ _ _ _ _, Node n2 _ _ _ _ _ _, NodeNode n1' n2' _) 
                   = foldl (.&&) (pgBool True) [ ((.==) n2 n2')
                                               , ((.==) (toNullable n1) n1')
                                               ]

-- | Left join to the ngram count per document
nodeNodeNgramLeftJoin :: Query (NodeRead, NodeNodeNgramReadNull)
nodeNodeNgramLeftJoin = leftJoin queryNodeTable queryNodeNodeNgramTable (eqNode)
     where
        eqNode (Node n1 _ _ _ _ _ _, NodeNodeNgram n1' _ _ _) = ((.==) n1 n1')


nodeNodeNgramLeftJoin' :: Column (Nullable PGInt4) 
                       -> Query (NodeRead, NodeNodeNgramReadNull)
nodeNodeNgramLeftJoin' nId = leftJoin queryNodeTable queryNodeNodeNgramTable (eqNode nId)
     where
        eqNode nId' (Node n1 _ _ _ _ _ _, NodeNodeNgram n1' n2 _ _) 
                 = (.&&) ((.==) n1 n1')
                         ((.==) nId' (toNullable n2))


leftJoin3 :: (Default NullMaker (columnsL1, nullableColumnsR) nullableColumnsR1,
Alexandre Delanoë's avatar
Alexandre Delanoë committed
185 186 187 188 189 190 191 192 193
              Default NullMaker columnsR nullableColumnsR,
              Default Unpackspec columnsR columnsR,
              Default Unpackspec nullableColumnsR nullableColumnsR,
              Default Unpackspec columnsL1 columnsL1,
              Default Unpackspec columnsL columnsL) =>
              Query columnsL1 -> Query columnsR -> Query columnsL
                -> ((columnsL1, columnsR) -> Column PGBool)
                -> ((columnsL, (columnsL1, nullableColumnsR)) -> Column PGBool)
                -> Query (columnsL, nullableColumnsR1)
194 195
leftJoin3 q1 q2 q3 cond12 cond23 = leftJoin q3 (leftJoin q1 q2 cond12) cond23

Alexandre Delanoë's avatar
Alexandre Delanoë committed
196

197 198 199
leftJoin3' :: Query (NodeRead, (NodeReadNull, NodeNodeNgramReadNull))
leftJoin3' = leftJoin3 queryNodeTable  queryNodeNodeNgramTable queryNodeTable cond12 cond23
    where
200 201
         cond12 (Node occId _ _ _ _ _ _, NodeNodeNgram occId' _ _ _)
                = (.==) occId occId'
Alexandre Delanoë's avatar
Alexandre Delanoë committed
202

203 204 205
         cond23 :: (NodeRead, (NodeRead, NodeNodeNgramReadNull)) -> Column PGBool
         cond23 (Node  docId _ _ _ _ _ _, (Node _ _ _ _ _ _ _, NodeNodeNgram _ docId' _ _))
                = (.||) ((.==) (toNullable docId) docId') (isNull docId')
Alexandre Delanoë's avatar
Alexandre Delanoë committed
206 207


208 209 210 211 212 213 214 215 216 217 218
leftJoin3''' :: Query (NodeRead, (NodeNodeReadNull, NodeReadNull))
leftJoin3''' = leftJoin3 queryNodeNodeTable queryNodeTable queryNodeTable cond12 cond23
    where
         cond12 (NodeNode favId _ _, Node favId' _ _ _ _ _ _)
                = (.||) ((.==) favId (toNullable favId')) (isNull $ toNullable favId)

         cond23 :: (NodeRead, (NodeNodeRead, NodeReadNull)) -> Column PGBool
         cond23 (Node  nId _ _ _ _ _ _, (NodeNode _ nId' _, Node _ _ _ _ _ _ _ ))
                = ((.==) (nId) (nId'))


219
-- | Building the facet
220
selectDocFacet' :: NodeType -> ParentId -> Maybe NodeType -> Query FacetDocRead
221
selectDocFacet' _ pId _ = proc () -> do
222
        (n1,(nn,n2)) <- leftJoin3''' -< ()
223 224
        restrict -< (.&&) (node_parentId n1 .== (toNullable $ pgInt4 pId))
                          (node_typename n1 .== (pgInt4 $ nodeTypeId Document))
225

226
        restrict -< (.||) (node_typename n2 .== (toNullable $ pgInt4 $ nodeTypeId Favorites))
227
                          (isNull $ node_typename n2)
228 229

        restrict -< (.||) (node_parentId n2 .== (toNullable $ pgInt4 $ nodeTypeId Favorites))
230 231 232
                          (isNull $ node_parentId n2)

        let isFav = ifThenElse (isNull $ nodeNode_score nn) (pgBool False) (pgBool True)
233

234
        returnA  -< FacetDoc (node_id n1) (node_date n1) (node_hyperdata n1) (isFav) (pgInt4 1)
235 236