{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DeriveFunctor #-}
{-# language GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedStrings #-}
{-# language DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
-- | Link-based datasets from https://linqs.soe.ucsc.edu/data
{-# options_ghc -Wno-unused-imports -Wno-unused-top-binds #-}
module Algebra.Graph.IO.Datasets.LINQS (
  restoreContent, CitesRow(..), ContentRow(..), 
  -- * Internal
  stash,
  sourceGraphEdges, loadGraph
                                       ) where

import Control.Applicative (Alternative(..))
import Control.Monad (when)
import Control.Monad.IO.Class (MonadIO(..))
import Data.Functor (($>), void)

import GHC.Generics (Generic(..))
import GHC.Int (Int16)

-- algebraic-graphs
import qualified Algebra.Graph as G (Graph, empty, overlay, edge)
-- bytestring
import Data.ByteString (ByteString)
import Data.ByteString.Char8 (unpack)
-- binary
import Data.Binary (Binary(..), encode, decode, encodeFile, decodeFileOrFail)
-- binary-conduit
import qualified Data.Conduit.Serialization.Binary as CB (conduitDecode, conduitEncode, ParseError(..))
-- conduit
import Conduit (MonadUnliftIO(..), MonadResource, runResourceT)
import Data.Conduit (runConduit, ConduitT, (.|), yield, await, runConduitRes)
import qualified Data.Conduit.Combinators as C (print, sourceFile, sinkFile, map, mapM, foldM, mapWhile, mapAccumWhile, foldMap, foldl, scanl)
-- containers
import Data.Sequence (Seq, (|>))
import qualified Data.Map as M (Map, singleton, lookup)
-- directory
import System.Directory (createDirectoryIfMissing)
-- exceptions
import Control.Monad.Catch (MonadThrow(..))
-- filepath
import System.FilePath ((</>), takeFileName, takeExtension)
-- http-conduit
import Network.HTTP.Simple (httpSource, getResponseBody, Response, Request, parseRequest, setRequestMethod)
-- megaparsec
import Text.Megaparsec (parse, runParserT)
import Text.Megaparsec.Char (char)
import Text.Megaparsec.Error (errorBundlePretty, ParseErrorBundle)
-- parser.combinators
import Control.Monad.Combinators (count)
-- tar-conduit
import Data.Conduit.Tar (Header(..), untarChunks, TarChunk, withEntries, FileInfo, filePath, withFileInfo, headerFileType, FileType(..), headerFilePath)
-- text
import qualified Data.Text as T (Text, unwords)



import Algebra.Graph.IO.Internal (fetch, unTarGz, Parser, ParserT, ParseE, symbol, lexeme, alphaNum)
import Algebra.Graph.IO.SV (parseTSV)

{-
CiteSeer: The CiteSeer dataset consists of 3312 scientific publications classified into one of six classes. The citation network consists of 4732 links. Each publication in the dataset is described by a 0/1-valued word vector indicating the absence/presence of the corresponding word from the dictionary. The dictionary consists of 3703 unique words. The README file in the dataset provides more details.
http://www.cs.umd.edu/~sen/lbc-proj/data/citeseer.tgz

Cora: The Cora dataset consists of 2708 scientific publications classified into one of seven classes. The citation network consists of 5429 links. Each publication in the dataset is described by a 0/1-valued word vector indicating the absence/presence of the corresponding word from the dictionary. The dictionary consists of 1433 unique words. The README file in the dataset provides more details.
http://www.cs.umd.edu/~sen/lbc-proj/data/cora.tgz

WebKB: The WebKB dataset consists of 877 scientific publications classified into one of five classes. The citation network consists of 1608 links. Each publication in the dataset is described by a 0/1-valued word vector indicating the absence/presence of the corresponding word from the dictionary. The dictionary consists of 1703 unique words. The README file in the dataset provides more details.
http://www.cs.umd.edu/~sen/lbc-proj/data/WebKB.tgz

-}


-- | Download, decompress, parse, serialize and save the dataset to local storage
stash :: (Binary c) =>
         FilePath -- ^ directory where the data files will be saved
      -> String -- ^ URI of .tar.gz file
      -> Int -- ^ dictionary size
      -> Parser c -- ^ document class
      -> IO ()
stash :: forall c. Binary c => String -> String -> Int -> Parser c -> IO ()
stash String
dir String
uri Int
n Parser c
pc = do
  Request
rq <- forall (m :: * -> *). MonadThrow m => String -> m Request
parseRequest String
uri
  Bool -> String -> IO ()
createDirectoryIfMissing Bool
True String
dir
  forall (m :: * -> *) a. MonadUnliftIO m => ResourceT m a -> m a
runResourceT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit forall a b. (a -> b) -> a -> b
$
    forall (m :: * -> *) i.
MonadResource m =>
Request -> ConduitT i ByteString m ()
fetch Request
rq forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
    forall (m :: * -> *).
(PrimMonad m, MonadThrow m) =>
ConduitT ByteString TarChunk m ()
unTarGz forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
    forall (m :: * -> *) o.
MonadThrow m =>
(FileInfo -> ConduitM ByteString o m ())
-> ConduitM TarChunk o m ()
withFileInfo ( \FileInfo
fi -> do
     forall (m :: * -> *) c o.
(MonadThrow m, MonadResource m, Binary c) =>
String -> Int -> Parser c -> FileInfo -> ConduitT ByteString o m ()
contentToFile String
dir Int
n Parser c
pc FileInfo
fi
     forall (m :: * -> *) c.
(MonadThrow m, MonadIO m, MonadResource m) =>
String -> FileInfo -> ConduitT ByteString c m ()
citesToFile String
dir FileInfo
fi )

-- | Load the graph node data from local storage
restoreContent :: (Binary c) => FilePath -- ^ directory where the data files are saved
               -> IO (M.Map String (Int16, Seq Int16, c))
restoreContent :: forall c.
Binary c =>
String -> IO (Map String (Int16, Seq Int16, c))
restoreContent String
dir = forall (m :: * -> *) a. MonadUnliftIO m => ResourceT m a -> m a
runResourceT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit forall a b. (a -> b) -> a -> b
$
  forall (m :: * -> *) c i.
(MonadResource m, MonadThrow m, Binary c) =>
String -> ConduitT i (ContentRow Int16 c) m ()
contentFromFile String
dir forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
  forall (m :: * -> *) b a o.
(Monad m, Monoid b) =>
(a -> b) -> ConduitT a o m b
C.foldMap ( \(CRow Int16
i String
k Seq Int16
fs c
c) -> forall k a. k -> a -> Map k a
M.singleton String
k (Int16
i, Seq Int16
fs, c
c) )


citesFromFile :: (MonadResource m, MonadThrow m) => FilePath -> ConduitT i (CitesRow String) m ()
citesFromFile :: forall (m :: * -> *) i.
(MonadResource m, MonadThrow m) =>
String -> ConduitT i (CitesRow String) m ()
citesFromFile String
dir =
  forall (m :: * -> *) i.
MonadResource m =>
String -> ConduitT i ByteString m ()
C.sourceFile (String
dir String -> String -> String
</> String
"cites") forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
  forall b (m :: * -> *).
(Binary b, MonadThrow m) =>
ConduitT ByteString b m ()
CB.conduitDecode

-- | Reconstruct the citation graph
--
-- NB : relies on the user having `stash`ed the dataset to local disk first.
loadGraph :: (Binary c) =>
             FilePath -- ^ directory where the data files were saved
          -> IO (G.Graph (ContentRow Int16 c))
loadGraph :: forall c. Binary c => String -> IO (Graph (ContentRow Int16 c))
loadGraph String
dir = do
  Map String (Int16, Seq Int16, c)
mm <- forall c.
Binary c =>
String -> IO (Map String (Int16, Seq Int16, c))
restoreContent String
dir
  forall (m :: * -> *) a. MonadUnliftIO m => ResourceT m a -> m a
runResourceT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit forall a b. (a -> b) -> a -> b
$
    forall (m :: * -> *) i.
(MonadResource m, MonadThrow m) =>
String -> ConduitT i (CitesRow String) m ()
citesFromFile String
dir forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
    forall (m :: * -> *) a b o.
Monad m =>
(a -> b -> a) -> a -> ConduitT b o m a
C.foldl (\Graph (ContentRow Int16 c)
gr (CitesRow String
b String
a) ->
               let
                 edm :: Maybe ((Int16, Seq Int16, c), (Int16, Seq Int16, c))
edm = (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup String
a Map String (Int16, Seq Int16, c)
mm forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup String
b Map String (Int16, Seq Int16, c)
mm
               in
                 case Maybe ((Int16, Seq Int16, c), (Int16, Seq Int16, c))
edm of
                   Maybe ((Int16, Seq Int16, c), (Int16, Seq Int16, c))
Nothing -> Graph (ContentRow Int16 c)
gr -- error $ show e
                   Just ((Int16
ib, Seq Int16
bffs, c
bc), (Int16
ia, Seq Int16
affs, c
ac)) ->
                     let
                       acr :: ContentRow Int16 c
acr = forall i c. i -> String -> Seq Int16 -> c -> ContentRow i c
CRow Int16
ia String
a Seq Int16
affs c
ac
                       bcr :: ContentRow Int16 c
bcr = forall i c. i -> String -> Seq Int16 -> c -> ContentRow i c
CRow Int16
ib String
b Seq Int16
bffs c
bc
                     in
                       (ContentRow Int16 c
acr forall a. a -> a -> Graph a
`G.edge` ContentRow Int16 c
bcr) forall a. Graph a -> Graph a -> Graph a
`G.overlay` Graph (ContentRow Int16 c)
gr
                ) forall a. Graph a
G.empty

-- | Stream out the edges of the citation graph, in which the nodes are decorated with the document metadata.
--
-- The full citation graph can be reconstructed by folding over this stream and `G.overlay`ing the graph edges as they arrive.
--
-- This way the graph can be partitioned in training , test and validation subsets at the usage site
sourceGraphEdges :: (MonadResource m, MonadThrow m) =>
                      FilePath -- ^ directory of data files
                   -> M.Map String (Int16, Seq Int16, c) -- ^ 'content' data
                   -> ConduitT i (Maybe (G.Graph (ContentRow Int16 c))) m ()
sourceGraphEdges :: forall (m :: * -> *) c i.
(MonadResource m, MonadThrow m) =>
String
-> Map String (Int16, Seq Int16, c)
-> ConduitT i (Maybe (Graph (ContentRow Int16 c))) m ()
sourceGraphEdges String
dir Map String (Int16, Seq Int16, c)
mm =
    forall (m :: * -> *) i.
(MonadResource m, MonadThrow m) =>
String -> ConduitT i (CitesRow String) m ()
citesFromFile String
dir forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
    forall (m :: * -> *) a b. Monad m => (a -> b) -> ConduitT a b m ()
C.map (\(CitesRow String
b String
a) ->
             case (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup String
a Map String (Int16, Seq Int16, c)
mm forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup String
b Map String (Int16, Seq Int16, c)
mm of
               Maybe ((Int16, Seq Int16, c), (Int16, Seq Int16, c))
Nothing -> forall a. Maybe a
Nothing
               Just ((Int16
ib, Seq Int16
bffs, c
bc), (Int16
ia, Seq Int16
affs, c
ac)) ->
                 let
                       acr :: ContentRow Int16 c
acr = forall i c. i -> String -> Seq Int16 -> c -> ContentRow i c
CRow Int16
ia String
a Seq Int16
affs c
ac
                       bcr :: ContentRow Int16 c
bcr = forall i c. i -> String -> Seq Int16 -> c -> ContentRow i c
CRow Int16
ib String
b Seq Int16
bffs c
bc
                 in forall a. a -> Maybe a
Just (ContentRow Int16 c
acr forall a. a -> a -> Graph a
`G.edge` ContentRow Int16 c
bcr))


-- | Pick out the 'content' file in the archive, parse its contents and serialize to disk
--
-- | NB : the integer node identifiers are serialized as Int16, so the graph can only have up to 65535 nodes.
--
-- Contact customer service if you need more node IDs.
contentToFile :: (MonadThrow m, MonadResource m, Binary c) =>
                 FilePath
              -> Int -- ^ dictionary size
              -> Parser c -- ^ document class
              -> FileInfo
              -> ConduitT ByteString o m ()
contentToFile :: forall (m :: * -> *) c o.
(MonadThrow m, MonadResource m, Binary c) =>
String -> Int -> Parser c -> FileInfo -> ConduitT ByteString o m ()
contentToFile String
dir Int
n Parser c
pc FileInfo
fi = forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ((String -> String
takeExtension forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
unpack forall a b. (a -> b) -> a -> b
$ FileInfo -> ByteString
filePath FileInfo
fi) forall a. Eq a => a -> a -> Bool
== String
".content") forall a b. (a -> b) -> a -> b
$ do
  forall (m :: * -> *).
MonadThrow m =>
ConduitT ByteString (Row Text) m ()
parseTSV forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
    forall (m :: * -> *) a b. Monad m => (a -> b) -> ConduitT a b m ()
C.map Row Text -> Text
T.unwords forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
    forall (f :: * -> *) a. Functor f => f a -> f ()
void (forall (m :: * -> *) a s b.
Monad m =>
(a -> s -> Either s (s, b)) -> s -> ConduitT a b m s
C.mapAccumWhile ( \Text
r Int16
i -> do
               case forall e s a.
Parsec e s a -> String -> s -> Either (ParseErrorBundle s e) a
parse (forall i c. i -> Int -> Parser c -> Parser (ContentRow i c)
contentRowP Int16
i Int
n Parser c
pc) String
"" Text
r of
                 Left ParseErrorBundle Text Void
e -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
errorBundlePretty ParseErrorBundle Text Void
e
                 Right ContentRow Int16 c
x -> forall a b. b -> Either a b
Right (forall a. Enum a => a -> a
succ Int16
i, ContentRow Int16 c
x) ) (Int16
0 :: Int16)
         ) forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
    forall b (m :: * -> *).
(Binary b, MonadThrow m) =>
ConduitT b ByteString m ()
CB.conduitEncode forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
    forall (m :: * -> *) o.
MonadResource m =>
String -> ConduitT ByteString o m ()
C.sinkFile (String
dir String -> String -> String
</> String
"content-z")

contentFromFile :: (MonadResource m, MonadThrow m, Binary c) => FilePath
                -> ConduitT i (ContentRow Int16 c) m ()
contentFromFile :: forall (m :: * -> *) c i.
(MonadResource m, MonadThrow m, Binary c) =>
String -> ConduitT i (ContentRow Int16 c) m ()
contentFromFile String
dir =
  forall (m :: * -> *) i.
MonadResource m =>
String -> ConduitT i ByteString m ()
C.sourceFile (String
dir String -> String -> String
</> String
"content-z") forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
  forall b (m :: * -> *).
(Binary b, MonadThrow m) =>
ConduitT ByteString b m ()
CB.conduitDecode


-- | Who cites whom
data CitesRow a = CitesRow {
  forall a. CitesRow a -> a
cirTo :: a -- ^ cited
  , forall a. CitesRow a -> a
cirFrom :: a -- ^ citing
  } deriving (CitesRow a -> CitesRow a -> Bool
forall a. Eq a => CitesRow a -> CitesRow a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CitesRow a -> CitesRow a -> Bool
$c/= :: forall a. Eq a => CitesRow a -> CitesRow a -> Bool
== :: CitesRow a -> CitesRow a -> Bool
$c== :: forall a. Eq a => CitesRow a -> CitesRow a -> Bool
Eq, Int -> CitesRow a -> String -> String
forall a. Show a => Int -> CitesRow a -> String -> String
forall a. Show a => [CitesRow a] -> String -> String
forall a. Show a => CitesRow a -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CitesRow a] -> String -> String
$cshowList :: forall a. Show a => [CitesRow a] -> String -> String
show :: CitesRow a -> String
$cshow :: forall a. Show a => CitesRow a -> String
showsPrec :: Int -> CitesRow a -> String -> String
$cshowsPrec :: forall a. Show a => Int -> CitesRow a -> String -> String
Show, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CitesRow a) x -> CitesRow a
forall a x. CitesRow a -> Rep (CitesRow a) x
$cto :: forall a x. Rep (CitesRow a) x -> CitesRow a
$cfrom :: forall a x. CitesRow a -> Rep (CitesRow a) x
Generic, forall a. Binary a => Get (CitesRow a)
forall a. Binary a => [CitesRow a] -> Put
forall a. Binary a => CitesRow a -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [CitesRow a] -> Put
$cputList :: forall a. Binary a => [CitesRow a] -> Put
get :: Get (CitesRow a)
$cget :: forall a. Binary a => Get (CitesRow a)
put :: CitesRow a -> Put
$cput :: forall a. Binary a => CitesRow a -> Put
Binary)

citesRowP :: Parser (CitesRow String)
citesRowP :: Parser (CitesRow String)
citesRowP = forall a. a -> a -> CitesRow a
CitesRow forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Parser a -> Parser a
lexeme Parser String
alphaNum forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Parser a -> Parser a
lexeme Parser String
alphaNum


-- | Dataset row of the .content file
--
-- The .content file contains descriptions of the papers in the following format:
--
-- 		\<paper_id\> \<word_attributes\> \<class_label\>
--
-- The first entry in each line contains the unique string ID of the paper followed by binary values indicating whether each word in the vocabulary is present (indicated by 1) or absent (indicated by 0) in the paper. Finally, the last entry in the line contains the class label of the paper.
data ContentRow i c = CRow {
  forall i c. ContentRow i c -> i
crId :: i -- ^ integer identifier
  , forall i c. ContentRow i c -> String
crIdStr :: String -- ^ identifier string
  , forall i c. ContentRow i c -> Seq Int16
crFeatures :: Seq Int16 -- ^ features, in sparse format (without the zeros)
  , forall i c. ContentRow i c -> c
crClass :: c -- ^ document class label
                   } deriving (ContentRow i c -> ContentRow i c -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall i c.
(Eq i, Eq c) =>
ContentRow i c -> ContentRow i c -> Bool
/= :: ContentRow i c -> ContentRow i c -> Bool
$c/= :: forall i c.
(Eq i, Eq c) =>
ContentRow i c -> ContentRow i c -> Bool
== :: ContentRow i c -> ContentRow i c -> Bool
$c== :: forall i c.
(Eq i, Eq c) =>
ContentRow i c -> ContentRow i c -> Bool
Eq, ContentRow i c -> ContentRow i c -> Bool
ContentRow i c -> ContentRow i c -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {i} {c}. (Ord i, Ord c) => Eq (ContentRow i c)
forall i c.
(Ord i, Ord c) =>
ContentRow i c -> ContentRow i c -> Bool
forall i c.
(Ord i, Ord c) =>
ContentRow i c -> ContentRow i c -> Ordering
forall i c.
(Ord i, Ord c) =>
ContentRow i c -> ContentRow i c -> ContentRow i c
min :: ContentRow i c -> ContentRow i c -> ContentRow i c
$cmin :: forall i c.
(Ord i, Ord c) =>
ContentRow i c -> ContentRow i c -> ContentRow i c
max :: ContentRow i c -> ContentRow i c -> ContentRow i c
$cmax :: forall i c.
(Ord i, Ord c) =>
ContentRow i c -> ContentRow i c -> ContentRow i c
>= :: ContentRow i c -> ContentRow i c -> Bool
$c>= :: forall i c.
(Ord i, Ord c) =>
ContentRow i c -> ContentRow i c -> Bool
> :: ContentRow i c -> ContentRow i c -> Bool
$c> :: forall i c.
(Ord i, Ord c) =>
ContentRow i c -> ContentRow i c -> Bool
<= :: ContentRow i c -> ContentRow i c -> Bool
$c<= :: forall i c.
(Ord i, Ord c) =>
ContentRow i c -> ContentRow i c -> Bool
< :: ContentRow i c -> ContentRow i c -> Bool
$c< :: forall i c.
(Ord i, Ord c) =>
ContentRow i c -> ContentRow i c -> Bool
compare :: ContentRow i c -> ContentRow i c -> Ordering
$ccompare :: forall i c.
(Ord i, Ord c) =>
ContentRow i c -> ContentRow i c -> Ordering
Ord, Int -> ContentRow i c -> String -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
forall i c.
(Show i, Show c) =>
Int -> ContentRow i c -> String -> String
forall i c.
(Show i, Show c) =>
[ContentRow i c] -> String -> String
forall i c. (Show i, Show c) => ContentRow i c -> String
showList :: [ContentRow i c] -> String -> String
$cshowList :: forall i c.
(Show i, Show c) =>
[ContentRow i c] -> String -> String
show :: ContentRow i c -> String
$cshow :: forall i c. (Show i, Show c) => ContentRow i c -> String
showsPrec :: Int -> ContentRow i c -> String -> String
$cshowsPrec :: forall i c.
(Show i, Show c) =>
Int -> ContentRow i c -> String -> String
Show, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall i c x. Rep (ContentRow i c) x -> ContentRow i c
forall i c x. ContentRow i c -> Rep (ContentRow i c) x
$cto :: forall i c x. Rep (ContentRow i c) x -> ContentRow i c
$cfrom :: forall i c x. ContentRow i c -> Rep (ContentRow i c) x
Generic, forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
forall i c. (Binary i, Binary c) => Get (ContentRow i c)
forall i c. (Binary i, Binary c) => [ContentRow i c] -> Put
forall i c. (Binary i, Binary c) => ContentRow i c -> Put
putList :: [ContentRow i c] -> Put
$cputList :: forall i c. (Binary i, Binary c) => [ContentRow i c] -> Put
get :: Get (ContentRow i c)
$cget :: forall i c. (Binary i, Binary c) => Get (ContentRow i c)
put :: ContentRow i c -> Put
$cput :: forall i c. (Binary i, Binary c) => ContentRow i c -> Put
Binary)

bit :: Parser Bool
bit :: Parser Bool
bit = (forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
'0' forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Bool
False) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
'1' forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Bool
True)

sparse :: Foldable t => t Bool -> Seq Int16
sparse :: forall (t :: * -> *). Foldable t => t Bool -> Seq Int16
sparse = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\(Seq Int16
acc, Int16
i) Bool
b -> if Bool
b then (Seq Int16
acc forall a. Seq a -> a -> Seq a
|> Int16
i, forall a. Enum a => a -> a
succ Int16
i) else (Seq Int16
acc, forall a. Enum a => a -> a
succ Int16
i)) (forall a. Monoid a => a
mempty, Int16
0)

contentRowP :: i -- ^ node identifier
            -> Int -- ^ vocabulary size
            -> Parser c -- ^ parser for document class
            -> Parser (ContentRow i c)
contentRowP :: forall i c. i -> Int -> Parser c -> Parser (ContentRow i c)
contentRowP i
i Int
n Parser c
dcp = do
  String
istr <- forall a. Parser a -> Parser a
lexeme Parser String
alphaNum
  Seq Int16
feats <- forall (t :: * -> *). Foldable t => t Bool -> Seq Int16
sparse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. Monad m => Int -> m a -> m [a]
count Int
n (forall a. Parser a -> Parser a
lexeme Parser Bool
bit)
  c
c <- forall a. Parser a -> Parser a
lexeme Parser c
dcp
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall i c. i -> String -> Seq Int16 -> c -> ContentRow i c
CRow i
i String
istr Seq Int16
feats c
c



citesToFile :: (MonadThrow m, MonadIO m, MonadResource m) =>
               FilePath
            -> FileInfo
            -> ConduitT ByteString c m ()
citesToFile :: forall (m :: * -> *) c.
(MonadThrow m, MonadIO m, MonadResource m) =>
String -> FileInfo -> ConduitT ByteString c m ()
citesToFile String
dir FileInfo
fi = do
  let fpath :: String
fpath = ByteString -> String
unpack forall a b. (a -> b) -> a -> b
$ FileInfo -> ByteString
filePath FileInfo
fi
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String -> String
takeExtension String
fpath forall a. Eq a => a -> a -> Bool
== String
".cites") forall a b. (a -> b) -> a -> b
$
    forall (m :: * -> *).
MonadThrow m =>
ConduitT ByteString (Row Text) m ()
parseTSV forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
    forall (m :: * -> *) a b. Monad m => (a -> b) -> ConduitT a b m ()
C.map Row Text -> Text
T.unwords forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
    forall (m :: * -> *) a b. Monad m => (a -> b) -> ConduitT a b m ()
C.map ( \Text
r -> case forall e s a.
Parsec e s a -> String -> s -> Either (ParseErrorBundle s e) a
parse Parser (CitesRow String)
citesRowP String
"" Text
r of
              Left ParseErrorBundle Text Void
e -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
errorBundlePretty ParseErrorBundle Text Void
e
              Right CitesRow String
x -> CitesRow String
x ) forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
    forall b (m :: * -> *).
(Binary b, MonadThrow m) =>
ConduitT b ByteString m ()
CB.conduitEncode forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.|
    forall (m :: * -> *) o.
MonadResource m =>
String -> ConduitT ByteString o m ()
C.sinkFile (String
dir String -> String -> String
</> String
"cites")