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

[PARSERS] RIS OK

parent 69bc5fe7
...@@ -17,7 +17,7 @@ citation programs to exchange data.[More](https://en.wikipedia.org/wiki/RIS_(fil ...@@ -17,7 +17,7 @@ citation programs to exchange data.[More](https://en.wikipedia.org/wiki/RIS_(fil
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Gargantext.Text.Parsers.RIS (risParser, field, notice) where module Gargantext.Text.Parsers.RIS (risParser) where
import Control.Applicative import Control.Applicative
import Data.Attoparsec.ByteString (Parser, try, string, takeTill, take, manyTill, many1, endOfInput) import Data.Attoparsec.ByteString (Parser, try, string, takeTill, take, manyTill, many1, endOfInput)
...@@ -34,46 +34,35 @@ data Lines = OneLine | MultiLine ...@@ -34,46 +34,35 @@ data Lines = OneLine | MultiLine
risParser :: Parser [[(ByteString, ByteString)]] risParser :: Parser [[(ByteString, ByteString)]]
risParser = do risParser = do
--_ <- manyTill anyChar (string $ pack "START") n <- notice "TY -"
ns <- many1 notice -- <* (string $ pack "\nXXX") ns <- many1 (notice "\nTY -")
pure ns pure $ [n] <> ns
notice :: Parser [(ByteString, ByteString)] notice :: Parser ByteString -> Parser [(ByteString, ByteString)]
notice = start *> many field <* end notice s = start *> many field <* end
where where
start :: Parser ByteString start :: Parser ByteString
start = "\nTY" *> takeTill isEndOfLine start = s *> takeTill isEndOfLine
end :: Parser ByteString end :: Parser ByteString
end = "\nER\n" *> takeTill isEndOfLine end = "\nER -" *> takeTill isEndOfLine
--end = manyTill anyChar (string $ pack "\nER\n")
fields :: Parser [(ByteString, ByteString)]
fields = many field
field :: Parser (ByteString, ByteString) field :: Parser (ByteString, ByteString)
field = do field = do
--name <- "\n" *> take 2 <* takeTill isEndOfLine -- " -"
name <- "\n" *> take 2 <* " - " name <- "\n" *> take 2 <* " - "
txt <- takeTill isEndOfLine -- " -" txt <- takeTill isEndOfLine
--name <- take 2
--txt <- takeTill isEndOfLine
{-
txts <- try lines txts <- try lines
let txts' = case DL.length txts > 0 of let txts' = case DL.length txts > 0 of
True -> txts True -> txts
False -> [] False -> []
pure (translate name, concat ([txt] <> txts')) pure (translate name, concat ([txt] <> txts'))
--}
pure (translate name, txt)
lines :: Parser [ByteString] lines :: Parser [ByteString]
lines = many line lines = many line
where where
line :: Parser ByteString line :: Parser ByteString
line = "\n " *> takeTill isEndOfLine line = "\n\n" *> takeTill isEndOfLine
translate :: ByteString -> ByteString translate :: ByteString -> ByteString
translate champs translate champs
......
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