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

[DATE] parser -> UTCTime

parent 18ceac9c
......@@ -169,12 +169,12 @@ executables:
main: Main.hs
source-dirs: bin/gargantext-server
ghc-options:
- -threaded
- -rtsopts
- -with-rtsopts=-N
- -O2
- -Wmissing-signatures
- -Wcompat
- -Wmissing-signatures
- -rtsopts
- -threaded
- -with-rtsopts=-N
dependencies:
- base
- containers
......@@ -232,11 +232,12 @@ tests:
main: Main.hs
source-dirs: src-doctest
ghc-options:
- -Werror
- -threaded
- -O2
- -Wcompat
- -Wmissing-signatures
- -rtsopts
- -threaded
- -with-rtsopts=-N
- -Wmissing-signatures
dependencies:
- doctest
- Glob
......
......@@ -25,8 +25,12 @@ module Gargantext.Core
-- - SP == spanish (not implemented yet)
--
-- ... add your language and help us to implement it (:
data Lang = EN | FR -- | DE | SP | CH
-- | All languages supported
-- TODO : DE | SP | CH
data Lang = EN | FR
deriving (Show, Eq, Ord, Bounded, Enum)
allLangs :: [Lang]
allLangs = [minBound ..]
......@@ -19,12 +19,13 @@ please follow the types.
-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PackageImports #-}
module Gargantext.Text.Parsers -- (parse, FileFormat(..))
module Gargantext.Text.Parsers (parse, FileFormat(..), clean)
where
import System.FilePath (FilePath(), takeExtension)
import Codec.Archive.Zip (withArchive, getEntry, getEntries)
import "zip" Codec.Archive.Zip (withArchive, getEntry, getEntries)
import Data.Either.Extra (partitionEithers)
import Data.List (concat)
......@@ -49,15 +50,13 @@ import Gargantext.Prelude
import Gargantext.Text.Parsers.WOS (wosParser)
------------------------------------------------------------------------
type ParseError = String
type Field = Text
type Document = DM.Map Field Text
type FilesParsed = DM.Map FilePath FileParsed
data FileParsed = FileParsed { _fileParsed_errors :: Maybe ParseError
, _fileParsed_result :: [Document]
} deriving (Show)
--type Field = Text
--type Document = DM.Map Field Text
--type FilesParsed = DM.Map FilePath FileParsed
--data FileParsed = FileParsed { _fileParsed_errors :: Maybe ParseError
-- , _fileParsed_result :: [Document]
-- } deriving (Show)
-- | According to the format of Input file,
......@@ -85,7 +84,7 @@ parse format path = do
-- | withParser:
-- According the format of the text, choosing the right parser.
-- According to the format of the text, choose the right parser.
-- TODO withParser :: FileFormat -> Parser [Document]
withParser :: FileFormat -> Parser [[(DB.ByteString, DB.ByteString)]]
withParser WOS = wosParser
......
This diff is collapsed.
......@@ -27,7 +27,7 @@ import Data.Text as T
import Data.Either
-- | Use case
-- >>> :{
-- :{
-- wikimediaFile <- BL.readFile "text.xml"
-- _ <- runConduit $ parseLBS def wikimediaFile
-- .| force "mediawiki required" parseMediawiki
......
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