corenlp-parser-0.1.0.1: Launches CoreNLP and parses the JSON output

Safe HaskellNone
LanguageHaskell2010

NLP.CoreNLP

Contents

Description

Module provides a handy wrapper around the CoreNLP project's command-line utility https://nlp.stanford.edu/software/corenlp.html , and a parser for some of its output formats.

Synopsis

Documentation

launchCoreNLP Source #

Arguments

:: FilePath

Path to the directory where you extracted the CoreNLP project

-> [Text]

List of inputs

-> IO [Either String Document]

List of parsed results

Launch CoreNLP with your inputs. This function will put every piece of Text in a separate file, launch CoreNLP subprocess, and parse the results

parseJsonDoc :: Text -> Either String Document Source #

Parse JSON output of CoreNLP. See headlines source for an example JSON input.

data Dependency Source #

Constructors

Dependency 

Instances

Eq Dependency Source # 
Show Dependency Source # 
Generic Dependency Source # 

Associated Types

type Rep Dependency :: * -> * #

ToJSON Dependency Source # 
FromJSON Dependency Source # 
type Rep Dependency Source # 

data Entitymention Source #

Instances

Eq Entitymention Source # 
Show Entitymention Source # 
Generic Entitymention Source # 

Associated Types

type Rep Entitymention :: * -> * #

ToJSON Entitymention Source # 
FromJSON Entitymention Source # 
type Rep Entitymention Source # 

data Token Source #

Instances

Eq Token Source # 

Methods

(==) :: Token -> Token -> Bool #

(/=) :: Token -> Token -> Bool #

Show Token Source # 

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Generic Token Source # 

Associated Types

type Rep Token :: * -> * #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

ToJSON Token Source # 
FromJSON Token Source # 
type Rep Token Source # 

data Sentence Source #

Instances

Eq Sentence Source # 
Show Sentence Source # 
Generic Sentence Source # 

Associated Types

type Rep Sentence :: * -> * #

Methods

from :: Sentence -> Rep Sentence x #

to :: Rep Sentence x -> Sentence #

ToJSON Sentence Source # 
FromJSON Sentence Source # 
type Rep Sentence Source # 

data Coref Source #

Instances

Eq Coref Source # 

Methods

(==) :: Coref -> Coref -> Bool #

(/=) :: Coref -> Coref -> Bool #

Show Coref Source # 

Methods

showsPrec :: Int -> Coref -> ShowS #

show :: Coref -> String #

showList :: [Coref] -> ShowS #

Generic Coref Source # 

Associated Types

type Rep Coref :: * -> * #

Methods

from :: Coref -> Rep Coref x #

to :: Rep Coref x -> Coref #

ToJSON Coref Source # 
FromJSON Coref Source # 
type Rep Coref Source # 
type Rep Coref = D1 * (MetaData "Coref" "NLP.CoreNLP" "corenlp-parser-0.1.0.1-EWKruYErjO4D4MHwOmh1RE" False) (C1 * (MetaCons "Coref" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "id") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "type_") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "number") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "gender") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "animacy") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "startIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "endIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "headIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "sentNum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "position") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Int])) (S1 * (MetaSel (Just Symbol "isRepresentativeMention") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))))))

Internal

test :: IO () Source #