corenlp-parser-0.2.0.0: 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 PennPOS Source #

Constructors

CC

Coordinating conjunction

CD

Cardinal number

DT

Determiner

EX

Existential *there*

FW

Foreign word

IN

Preposition or subordinating conjunction

JJ

Adjective

JJR

Adjective, comparative

JJS

Adjective, superlative

LS

List item marker

MD

Modal

NN

Noun, singular or mass

NNS

Noun, plural

NNP

Proper noun, singular

NNPS

Proper noun, plural

PDT

Predeterminer

POS

Possessive ending

PRP

Personal pronoun

PRPDollar

Possessive pronoun

RB

Adverb

RBR

Adverb, comparative

RBS

Adverb, superlative

RP

Particle

SYM

Symbol

TO
  • to*
UH

Interjection

VB

Verb, base form

VBD

Verb, past tense

VBG

Verb, gerund or present participle

VBN

Verb, past participle

VBP

Verb, non-3rd person singular present

VBZ

Verb, 3rd person singular present

WDT

Wh-determiner

WP

Wh-pronoun

WPDollar

Possessive wh-pronoun

WRB

Wh-adverb

LRB

"-LRB-"? No idea what's this

RRB

"-RRB-"? No idea what's this

PosPunctuation Text

anyOf ".:,''$#$,", sometimes few together

Instances

Eq PennPOS Source # 

Methods

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

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

Show PennPOS Source # 
Generic PennPOS Source # 

Associated Types

type Rep PennPOS :: * -> * #

Methods

from :: PennPOS -> Rep PennPOS x #

to :: Rep PennPOS x -> PennPOS #

ToJSON PennPOS Source # 
FromJSON PennPOS Source # 
type Rep PennPOS Source # 
type Rep PennPOS = D1 * (MetaData "PennPOS" "NLP.CoreNLP" "corenlp-parser-0.2.0.0-67s34LB9YJQ1yYzRV8H2Hu" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CC" PrefixI False) (U1 *)) (C1 * (MetaCons "CD" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "DT" PrefixI False) (U1 *)) (C1 * (MetaCons "EX" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "FW" PrefixI False) (U1 *)) (C1 * (MetaCons "IN" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "JJ" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "JJR" PrefixI False) (U1 *)) (C1 * (MetaCons "JJS" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "LS" PrefixI False) (U1 *)) (C1 * (MetaCons "MD" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NN" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NNS" PrefixI False) (U1 *)) (C1 * (MetaCons "NNP" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NNPS" PrefixI False) (U1 *)) (C1 * (MetaCons "PDT" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "POS" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PRP" PrefixI False) (U1 *)) (C1 * (MetaCons "PRPDollar" PrefixI False) (U1 *))))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "RB" PrefixI False) (U1 *)) (C1 * (MetaCons "RBR" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "RBS" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "RP" PrefixI False) (U1 *)) (C1 * (MetaCons "SYM" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "TO" PrefixI False) (U1 *)) (C1 * (MetaCons "UH" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "VB" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "VBD" PrefixI False) (U1 *)) (C1 * (MetaCons "VBG" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "VBN" PrefixI False) (U1 *)) (C1 * (MetaCons "VBP" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "VBZ" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "WDT" PrefixI False) (U1 *)) (C1 * (MetaCons "WP" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "WPDollar" PrefixI False) (U1 *)) (C1 * (MetaCons "WRB" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LRB" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "RRB" PrefixI False) (U1 *)) (C1 * (MetaCons "PosPunctuation" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))))))))

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.2.0.0-67s34LB9YJQ1yYzRV8H2Hu" 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)))))))

data NamedEntity Source #

See https://stanfordnlp.github.io/CoreNLP/ner.html

Instances

Eq NamedEntity Source # 
Show NamedEntity Source # 
Generic NamedEntity Source # 

Associated Types

type Rep NamedEntity :: * -> * #

ToJSON NamedEntity Source # 
FromJSON NamedEntity Source # 
type Rep NamedEntity Source # 
type Rep NamedEntity = D1 * (MetaData "NamedEntity" "NLP.CoreNLP" "corenlp-parser-0.2.0.0-67s34LB9YJQ1yYzRV8H2Hu" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "PERSON" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "LOCATION" PrefixI False) (U1 *)) (C1 * (MetaCons "ORGANIZATION" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "MISC" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "MONEY" PrefixI False) (U1 *)) (C1 * (MetaCons "NUMBER" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "ORDINAL" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PERCENT" PrefixI False) (U1 *)) (C1 * (MetaCons "DATE" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "TIME" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "DURATION" PrefixI False) (U1 *)) (C1 * (MetaCons "SET" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "EMAIL" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "URL" PrefixI False) (U1 *)) (C1 * (MetaCons "CITY" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "STATE_OR_PROVINCE" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "COUNTRY" PrefixI False) (U1 *)) (C1 * (MetaCons "NATIONALITY" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "RELIGION" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TITLE" PrefixI False) (U1 *)) (C1 * (MetaCons "IDEOLOGY" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "CRIMINAL_CHARGE" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CAUSE_OF_DEATH" PrefixI False) (U1 *)) (C1 * (MetaCons "O" PrefixI False) (U1 *)))))))

Internal

test :: IO () Source #