Commit 193325e6 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[APP] command line options added.

parent f0e3a45b
{-|
Module : Main.hs
Description : Gargantext starter
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
module Main where module Main where
import Options.Generic
import Data.Text (unpack)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.API (startGargantext) import Gargantext.API (startGargantext, startGargantextMock)
import Text.Read (read)
import System.Environment (getArgs) ------------------------------------------------------
data Mode = Dev | Mock | Prod
deriving (Show, Read, Generic)
instance ParseRecord Mode
instance ParseField Mode
instance ParseFields Mode
data MyOptions = MyOptions { port :: Maybe Int
, iniFile :: Maybe Text
, mode :: Maybe Mode
}
deriving (Generic, Show)
instance ParseRecord MyOptions
main :: IO () main :: IO ()
main = do main = do
(port:iniFile:_) <- getArgs MyOptions myPort myIniFile myMode <- getRecord
startGargantext (read port :: Int) iniFile "Gargantext: collaborative platform for text-mining"
let myPort' = case myPort of
Just p -> p
Nothing -> 8008
let start = case myMode of
--Nothing -> startGargantext myPort' (unpack myIniFile')
Just Prod -> startGargantext myPort' (unpack myIniFile')
where
myIniFile' = case myIniFile of
Nothing -> panic "Need gargantext.ini file"
Just i -> i
Just Mock -> startGargantextMock myPort'
_ -> startGargantextMock myPort'
start
...@@ -130,6 +130,7 @@ executable: ...@@ -130,6 +130,7 @@ executable:
- ini - ini
- base - base
- unordered-containers - unordered-containers
- optparse-generic
tests: tests:
garg-test: garg-test:
......
...@@ -21,7 +21,8 @@ Portability : POSIX ...@@ -21,7 +21,8 @@ Portability : POSIX
{-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE NoMonomorphismRestriction #-}
------------------------------------------------------------------------ ------------------------------------------------------------------------
module Gargantext.Database.Facet where module Gargantext.Database.Facet
where
------------------------------------------------------------------------ ------------------------------------------------------------------------
import Prelude hiding (null, id, map, sum, not) import Prelude hiding (null, id, map, sum, not)
...@@ -68,8 +69,15 @@ data Facet id created hyperdata favorite ngramCount = ...@@ -68,8 +69,15 @@ data Facet id created hyperdata favorite ngramCount =
, facetDoc_ngramCount :: ngramCount , facetDoc_ngramCount :: ngramCount
} deriving (Show, Generic) } deriving (Show, Generic)
-- | JSON instance
$(deriveJSON (unPrefix "facetDoc_") ''Facet) $(deriveJSON (unPrefix "facetDoc_") ''Facet)
-- | Documentation instance
instance ToSchema FacetDoc
-- | Mock and Quickcheck instances
instance Arbitrary FacetDoc where instance Arbitrary FacetDoc where
arbitrary = elements [ FacetDoc id' (jour year 01 01) hp fav ngramCount arbitrary = elements [ FacetDoc id' (jour year 01 01) hp fav ngramCount
| id' <- [1..10] | id' <- [1..10]
...@@ -80,18 +88,16 @@ instance Arbitrary FacetDoc where ...@@ -80,18 +88,16 @@ instance Arbitrary FacetDoc where
] ]
-- Facets / Views for the Front End -- Facets / Views for the Front End
-- | Database instances
$(makeAdaptorAndInstance "pFacetDoc" ''Facet)
$(makeLensesWith abbreviatedFields ''Facet)
type FacetDocRead = Facet (Column PGInt4 ) type FacetDocRead = Facet (Column PGInt4 )
(Column PGTimestamptz) (Column PGTimestamptz)
(Column PGJsonb ) (Column PGJsonb )
(Column PGBool ) (Column PGBool )
(Column PGInt4 ) (Column PGInt4 )
instance ToSchema FacetDoc
$(makeAdaptorAndInstance "pFacetDoc" ''Facet)
$(makeLensesWith abbreviatedFields ''Facet)
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
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