]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Text/Parsers/WOS.hs
[FIX] build ok.
[gargantext.git] / src / Gargantext / Text / Parsers / WOS.hs
1 {-|
2 Module : Gargantext.Text.Parsers.WOS
3 Description :
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 Here is a longer description of this module, containing some
11 commentary with @some markup@.
12 -}
13
14 {-# LANGUAGE NoImplicitPrelude #-}
15 {-# LANGUAGE OverloadedStrings #-}
16
17 module Gargantext.Text.Parsers.WOS (wosParser) where
18
19 -- TOFIX : Should import Gargantext.Prelude here
20 import Prelude hiding (takeWhile, take, concat, readFile, lines, concat)
21
22 import qualified Data.List as DL
23
24 import Data.Monoid ((<>))
25 import Data.Attoparsec.ByteString (Parser, try, string
26 , takeTill, take
27 , manyTill, many1)
28 import Data.Attoparsec.ByteString.Char8 (anyChar, isEndOfLine)
29 import Data.ByteString (ByteString, concat)
30 import Data.ByteString.Char8 (pack)
31 import Control.Applicative
32
33 -------------------------------------------------------------
34
35
36
37
38 -- | wosParser parses ISI format from
39 -- Web Of Science Database
40 wosParser :: Parser [[(ByteString, ByteString)]]
41 wosParser = do
42 -- TODO Warning if version /= 1.0
43 -- FIXME anyChar (string ..) /= exact string "\nVR 1.0" ?
44 _ <- manyTill anyChar (string $ pack "\nVR 1.0")
45 ns <- many1 notice <* (string $ pack "\nEF" )
46 pure ns
47
48 notice :: Parser [(ByteString, ByteString)]
49 notice = start *> fields <* end
50 where
51 start :: Parser ByteString
52 start = "\nPT " *> takeTill isEndOfLine
53
54 end :: Parser [Char]
55 end = manyTill anyChar (string $ pack "\nER\n")
56
57
58 fields :: Parser [(ByteString, ByteString)]
59 fields = many field
60 where
61 field :: Parser (ByteString, ByteString)
62 field = do
63 name <- "\n" *> take 2 <* " "
64 txt <- takeTill isEndOfLine
65 txts <- try lines
66 let txts' = case DL.length txts > 0 of
67 True -> txts
68 False -> []
69 pure (translate name, concat ([txt] <> txts'))
70
71
72 lines :: Parser [ByteString]
73 lines = many line
74 where
75 line :: Parser ByteString
76 line = "\n " *> takeTill isEndOfLine
77
78 translate :: ByteString -> ByteString
79 translate champs
80 | champs == "AF" = "authors"
81 | champs == "TI" = "title"
82 | champs == "SO" = "source"
83 | champs == "DI" = "doi"
84 | champs == "PD" = "publication_date"
85 | champs == "AB" = "abstract"
86 | otherwise = champs
87 -------------------------------------------------------------
88