Commit 64e0bc84 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[PARSERS] refactor.

parent c41cdec8
......@@ -19,7 +19,7 @@ citation programs to exchange data.
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Text.Parsers.RIS (risParser, withField) where
module Gargantext.Text.Parsers.RIS (risParser, withField, fieldWith, lines) where
import Data.Either (either)
import Data.List (lookup)
......@@ -41,17 +41,21 @@ risParser = do
pure $ [n] <> ns
notice :: Parser ByteString -> Parser [(ByteString, ByteString)]
notice s = start *> many field <* end
notice s = start *> many (fieldWith field) <* end
where
field :: Parser ByteString
field = "\n" *> take 2 <* " - "
start :: Parser ByteString
start = s *> takeTill isEndOfLine
end :: Parser ByteString
end = "\nER -" *> takeTill isEndOfLine
field :: Parser (ByteString, ByteString)
field = do
name <- "\n" *> take 2 <* " - "
fieldWith :: Parser ByteString -> Parser (ByteString, ByteString)
fieldWith n = do
name <- n
txt <- takeTill isEndOfLine
txts <- try lines
let txts' = case DL.length txts > 0 of
......@@ -59,6 +63,7 @@ field = do
False -> []
pure (name, concat ([txt] <> txts'))
lines :: Parser [ByteString]
lines = many line
where
......
......@@ -29,6 +29,7 @@ import Data.Attoparsec.ByteString.Char8 (anyChar, isEndOfLine)
import Data.ByteString (ByteString, concat)
import Data.ByteString.Char8 (pack)
import Control.Applicative
import Gargantext.Text.Parsers.RIS (fieldWith, lines)
-------------------------------------------------------------
-- | wosParser parses ISI format from
......@@ -42,8 +43,11 @@ wosParser = do
pure ns
notice :: Parser [(ByteString, ByteString)]
notice = start *> fields <* end
notice = start *> many (fieldWith field) <* end
where
field :: Parser ByteString
field = "\n" *> take 2 <* " "
start :: Parser ByteString
start = "\nPT " *> takeTill isEndOfLine
......@@ -51,26 +55,6 @@ notice = start *> fields <* end
end = manyTill anyChar (string $ pack "\nER\n")
fields :: Parser [(ByteString, ByteString)]
fields = many field
where
field :: Parser (ByteString, ByteString)
field = do
name <- "\n" *> take 2 <* " "
txt <- takeTill isEndOfLine
txts <- try lines
let txts' = case DL.length txts > 0 of
True -> txts
False -> []
pure (translate name, concat ([txt] <> txts'))
lines :: Parser [ByteString]
lines = many line
where
line :: Parser ByteString
line = "\n " *> takeTill isEndOfLine
translate :: ByteString -> ByteString
translate champs
| champs == "AF" = "authors"
......
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