Types.hs 1.64 KB
Newer Older
1 2 3 4 5 6 7 8 9 10 11
{-|
Module      : Gargantext.Database.Types
Description : Specific Types to manage core Gargantext type with database
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX

-}

12
{-# OPTIONS_GHC -fno-warn-orphans #-}
13 14 15 16 17
{-# LANGUAGE TemplateHaskell        #-}

module Gargantext.Database.Types
  where

18
import Data.Hashable (Hashable)
19
import Gargantext.Core.Text (HasText(..))
20
import Gargantext.Database.Schema.Prelude
21
import Gargantext.Prelude
22 23 24 25
import qualified Database.PostgreSQL.Simple as PGS


-- | Index memory of any type in Gargantext
26
data Indexed i a =
27 28
  Indexed { _index     :: !i
          , _unIndex   :: !a
29 30 31 32 33
          }
  deriving (Show, Generic, Eq, Ord)

makeLenses ''Indexed

34 35
----------------------------------------------------------------------
-- | Main instances
36
instance (FromField i, FromField a) => PGS.FromRow (Indexed i a) where
37 38
  fromRow = Indexed <$> field <*> field

39 40 41 42
instance HasText a => HasText (Indexed i a)
  where
    hasText (Indexed _ a) = hasText a

43
instance (Hashable a, Hashable b) => Hashable (Indexed a b)
44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59

instance DefaultFromField (Nullable SqlInt4)   Int            where
    defaultFromField = fromPGSFromField

instance DefaultFromField (Nullable SqlFloat8) Int            where
    defaultFromField = fromPGSFromField

instance DefaultFromField (Nullable SqlFloat8) Double         where
    defaultFromField = fromPGSFromField

instance DefaultFromField SqlFloat8            (Maybe Double) where
    defaultFromField = fromPGSFromField

instance DefaultFromField SqlInt4              (Maybe Int)    where
    defaultFromField = fromPGSFromField