haskell-conll-0.1.0.1: Core Types for NLP

Safe HaskellNone
LanguageHaskell2010

Model.UniversalTreebank

Synopsis

Documentation

data REL Source #

Tags from Universal Dependencies project see `http://universaldependencies.org/en/dep/`

Constructors

Acl

clausal modifier of noun

Acl_Relcl (SpelledAs "acl:relcl")

relative clause modifier

Advcl

adverbial clause modifier

Advmod

adverbial modifier

Amod

adjectival modifier

Appos

appositional modifier

Aux

auxiliary

Auxpass

passive auxiliary

Case

case marking

Cc

coordination

Cc_Preconj (SpelledAs "cc:preconj")

preconjunct

Ccomp

clausal complement

Compound

compound

Compound_Pr (SpelledAs "compound:prt")

phrasal verb particle

Conj

conjunct

Cop

copula

Csubj

clausal subject

Csubjpass

clausal passive subject

Dep

dependent

Det

determiner

Det_Predet (SpelledAs "det:predet")

predeterminer

Discourse

discourse element

Dislocated

dislocated elements

Dobj

direct object

Expl

expletive

Fixed (SpelledAs "mwe")

multi-word expression

Flat

name

Foreign

foreign words

Goeswith

goes with

Iobj

indirect object

List

list

Mark

marker

Neg

negation modifier

Nmod

nominal modifier

Nmod_npmod (SpelledAs "nmod:npmod")

noun phrase as adverbial modifier

Nmod_poss (SpelledAs "nmod:poss")

possessive nominal modifier

Nmod_tmod (SpelledAs "nmod:tmod")

temporal modifier

Nsubj

nominal subject

Nsubjpass

passive nominal subject

Nummod

numeric modifier

Orphan

remnant in ellipsis

Parataxis

parataxis

Punct

punctuation

Reparandum

overridden disfluency

ROOT

root

Root

root (not main)

Vocative

vocative

Xcomp

open clausal complement

Unknown

unknown

Instances

Eq REL Source # 

Methods

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

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

Ord REL Source # 

Methods

compare :: REL -> REL -> Ordering #

(<) :: REL -> REL -> Bool #

(<=) :: REL -> REL -> Bool #

(>) :: REL -> REL -> Bool #

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

max :: REL -> REL -> REL #

min :: REL -> REL -> REL #

Read REL Source # 
Show REL Source # 

Methods

showsPrec :: Int -> REL -> ShowS #

show :: REL -> String #

showList :: [REL] -> ShowS #

Generic REL Source # 

Associated Types

type Rep REL :: * -> * #

Methods

from :: REL -> Rep REL x #

to :: Rep REL x -> REL #

TagLabel REL Source # 
type Rep REL Source # 
type Rep REL = D1 (MetaData "REL" "Model.UniversalTreebank" "haskell-conll-0.1.0.1-4fgvsJ3fTBg3ezTP62X73d" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Acl" PrefixI False) U1) ((:+:) (C1 (MetaCons "Acl_Relcl" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SpelledAs "acl:relcl")))) (C1 (MetaCons "Advcl" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Advmod" PrefixI False) U1) ((:+:) (C1 (MetaCons "Amod" PrefixI False) U1) (C1 (MetaCons "Appos" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Aux" PrefixI False) U1) ((:+:) (C1 (MetaCons "Auxpass" PrefixI False) U1) (C1 (MetaCons "Case" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Cc" PrefixI False) U1) ((:+:) (C1 (MetaCons "Cc_Preconj" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SpelledAs "cc:preconj")))) (C1 (MetaCons "Ccomp" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Compound" PrefixI False) U1) ((:+:) (C1 (MetaCons "Compound_Pr" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SpelledAs "compound:prt")))) (C1 (MetaCons "Conj" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Cop" PrefixI False) U1) ((:+:) (C1 (MetaCons "Csubj" PrefixI False) U1) (C1 (MetaCons "Csubjpass" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Dep" PrefixI False) U1) ((:+:) (C1 (MetaCons "Det" PrefixI False) U1) (C1 (MetaCons "Det_Predet" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SpelledAs "det:predet")))))) ((:+:) (C1 (MetaCons "Discourse" PrefixI False) U1) ((:+:) (C1 (MetaCons "Dislocated" PrefixI False) U1) (C1 (MetaCons "Dobj" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Expl" PrefixI False) U1) ((:+:) (C1 (MetaCons "Fixed" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SpelledAs "mwe")))) (C1 (MetaCons "Flat" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Foreign" PrefixI False) U1) ((:+:) (C1 (MetaCons "Goeswith" PrefixI False) U1) (C1 (MetaCons "Iobj" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "List" PrefixI False) U1) ((:+:) (C1 (MetaCons "Mark" PrefixI False) U1) (C1 (MetaCons "Neg" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Nmod" PrefixI False) U1) ((:+:) (C1 (MetaCons "Nmod_npmod" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SpelledAs "nmod:npmod")))) (C1 (MetaCons "Nmod_poss" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SpelledAs "nmod:poss")))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Nmod_tmod" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SpelledAs "nmod:tmod")))) ((:+:) (C1 (MetaCons "Nsubj" PrefixI False) U1) (C1 (MetaCons "Nsubjpass" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Nummod" PrefixI False) U1) ((:+:) (C1 (MetaCons "Orphan" PrefixI False) U1) (C1 (MetaCons "Parataxis" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Punct" PrefixI False) U1) ((:+:) (C1 (MetaCons "Reparandum" PrefixI False) U1) (C1 (MetaCons "ROOT" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Root" PrefixI False) U1) (C1 (MetaCons "Vocative" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Xcomp" PrefixI False) U1) (C1 (MetaCons "Unknown" PrefixI False) U1)))))))