! Divvun & Giellatekno - open source grammar for Lule Sámi ! Copyright © 2000-2015 The University of Tromsø & the Norwegian Sámi Parliament ! http://giellatekno.uit.no & http://divvun.no ! ! This program is free software; you can redistribute and/or modify ! this file under the terms of the GNU General Public License as published by ! the Free Software Foundation, either version 3 of the License, or ! (at your option) any later version. The GNU General Public License ! is found at http://www.gnu.org/licenses/gpl.html. It is ! also available in the file $GTHOME/LICENSE.txt. ! ! Other licensing options are available upon request, please contact ! giellatekno@uit.no or feedback@divvun.no ! ========================================================================== ! !! !!!Lule Sámi morphological analyser ! ========================================================================== ! Multichar_Symbols !!≈ Definitions for @CODE@ !! !!Tags for POS +N !!≈ * @CODE@ Noun +A !!≈ * @CODE@ Adjective +Adv !!≈ * @CODE@ Adverb +V !!≈ * @CODE@ Verb +Pron !!≈ * @CODE@ Pronouns +CS !!≈ * @CODE@ Subjunction +CC !!≈ * @CODE@ Conjunction +Adp !!≈ * @CODE@ Adposition +Po !!≈ * @CODE@ Postposition +Pr !!≈ * @CODE@ Preposition +Interj !!≈ * @CODE@ Interjection +Pcle !!≈ * @CODE@ Particle +Num !!≈ * @CODE@ Numeral ! Tags for sub-POS +Prop !!≈ * @CODE@ Propernouns +ACR !!≈ * @CODE@ Acronym ! Pronoun subtypes +Pers !!≈ * @CODE@ Personal pronoun +Dem !!≈ * @CODE@ Demonstrative pronoun +Interr !!≈ * @CODE@ Interrogative pronoun +Refl !!≈ * @CODE@ reflexive pronoun +Recipr !!≈ * @CODE@ reciprocal pronoun +Rel !!≈ * @CODE@ relative pronoun +Indef !!≈ * @CODE@ indefinite pronoun +Coll !!≈ * @CODE@ collective numerals +Arab !!≈ * @CODE@ arabic numerals +Rom !!≈ * @CODE@ remertall ! Usage tags +Err/Orth !!≈ * @CODE@ Substandard. An ungrammatical, non-normative form of normative lemma. +Err/Lex !!≈ * @CODE@ No normative lemma, often ungrammatical compounds like "bajásbuollda" and "songdebutierit". +Err/Der !!≈ * @CODE@ Lemmas that break with regular derivation rules, both morphologically and semantically +Use/Marg !!≈ * @CODE@ Marginal, but normative lemmas. Not in speller. +Use/-Spell !!≈ * @CODE@ Excluded from speller +Use/-PLX !!≈ * @CODE@ Excluded from PLX speller +Use/SpellNoSugg !!≈ * @CODE@ Recognized, but not suggested in speller +Use/Circ !!≈ * @CODE@ Circular path +Use/CircN !!≈ * @CODE@ Circular number path +Use/Ped !!≈ * @CODE@ Remove from pedagogical speller +Use/NG !!≈ * @CODE@ Do not generate, only for Oahpa and MT. In speller. +Use/MT !!= * __@CODE@__ Generate for MT only, for restricting analyses needed +Use/NGminip !!= * __@CODE@__ Not for miniparadigm in VD dicts +Use/NotDNorm !!≈ * @CODE@ For words without formal normalization. !! Divvun suggest that this shouldn't be normative. +Use/DNorm !!≈ * @CODE@ For words without formal normalization. !! Divvun suggest that this should be normative. Included in speller. ! Dialect tags: +Area/SE !!≈ * @CODE@ In Sweden +Area/NO !!≈ * @CODE@ In Norway +Dial/N !!≈ * @CODE@ Used in the northern areas. Some might say that !! these words are sme-words, but they are used by lulesamis in !! the northern part of the dialect area. Words like "válmas" +Dial/S !!≈ * @CODE@ Used in the southern areas +Dial/SH !!≈ * @CODE@ Short forms !! !Compounding tags !! The tags are of the following form: !! * __+CmpNP/xxx__ - Normative (N), Position (P), ie. the tag describes what !! position the tagged word can be in in a compound !! * __+CmpN/xxx__ - Normative (N) __form__ ie. the tag describes what !! form the tagged word should use when making compounds !! * __+Cmp/xxx__ - Descriptive compounding tags, ie. tags that''describes'' !! what form a word actually is using in a compound !! Normative/prescriptive compounding tags: !! (to govern compound behaviour for the speller, ie. what a compound SHOULD BE) !! The first part of the component may be .. +CmpN/Sg !!≈ * @CODE@ = Singular +CmpN/SgN !!≈ * @CODE@ = Singular Nominative +CmpN/SgG !!≈ * @CODE@ = Singular Genitive +CmpN/PlG !!≈ * @CODE@ = Plural Genitive ! This part of the component can .. +CmpNP/All !!≈ * @CODE@ - ... be in all positions, __default__, this tag does not have to be written +CmpNP/First !!≈ * @CODE@ - ... only be first part in a compound or alone +CmpNP/Pref !!≈ * @CODE@ - ... only __first__ part in a compound, NEVER alone +CmpNP/Last !!≈ * @CODE@ - ... only be last part in a compound or alone +CmpNP/Suff !!≈ * @CODE@ - ... only __last__ part in a compound, NEVER alone +CmpNP/None !!≈ * @CODE@ - ... not take part in compounds +CmpNP/Only !!≈ * @CODE@ - ... only be part of a compound, i.e. can never !! be used alone, but can appear in any position ! The second part of the compound may require that the previous (left part) is (and thus overrides the regular CmpN tags): +CmpN/SgLeft !!≈ * @CODE@ Singular to the left +CmpN/SgNomLeft !!≈ * @CODE@ Singular nominative to the left +CmpN/SgGenLeft !!≈ * @CODE@ Singular genitive to the left +CmpN/PlGenLeft !!≈ * @CODE@ Plural genitive to the left ! But these tags can again be overriden by the first word in a compound, if this part of the compound is tagged with a def tag: +CmpN/Def !!≈ * @CODE@ Left override +CmpN/DefSgGen !!≈ * @CODE@ Overrides left tag, requires SgGen form +CmpN/DefPlGen !!≈ * @CODE@ Overrides left tag, requires PlGen form ! Descriptive compounding tags: ! Tags for compound analysis - this is what a compound actually is: +Cmp/Sg !!≈ * __@CODE@__ Singular +Cmp/SgNom !!≈ * __@CODE@__ Singular Nominative +Cmp/SgGen !!≈ * __@CODE@__ Singular Genitive +Cmp/PlGen !!≈ * __@CODE@__ Plural Genitiv +Cmp/PlNom !!≈ * __@CODE@__ Plural Nominative +Cmp/Attr !!≈ * __@CODE@__ Attribute +Cmp !!≈ * __@CODE@__ Dynamic compound - this tag should always be part of a !! dynamic compound. !! It is important for Apertium, and useful in other cases as well. +Cmp/SplitR !!≈ * __@CODE@__ This is a split compound with the other part to the right: !! "Arbeids- og inkluderingsdepartementet" => Arbeids- = +Cmp/SplitR +Cmp/SplitL !!≈ * __@CODE@__ This is a split compound with the other part to the left +Cmp/Sh !!≈ * __@CODE@__ testing ShCmp ! ! ! ! === Tags for Inflection === ! Tags for Case and Number Inflection +Sg !!= * @CODE@ Singular number +Du !!= * @CODE@ Dual number +Pl !!= * @CODE@ Plural number +Ess !!= * @CODE@ Essive case +Nom !!= * @CODE@ Nominative case +Gen !!= * @CODE@ Genitive case +Acc !!= * @CODE@ Accusative case +Ill !!= * @CODE@ Illative case +Loc !!= * @CODE@ Locative case +Com !!= * @CODE@ Comitative case +Ine !!= * @CODE@ Inesive case +Ela !!= * @CODE@ Elative case +Par !!= * @CODE@ Partitive case +Abe !!= * @CODE@ Abessive case ! Possessive tags +PxSg1 !!= * @CODE@ possessive suffix singular first person +PxSg2 !!= * @CODE@ possessive suffix singular second person +PxSg3 !!= * @CODE@ possessive suffix singular third person +PxDu1 !!= * @CODE@ possessive suffix dual first person +PxDu2 !!= * @CODE@ possessive suffix dual second person +PxDu3 !!= * @CODE@ possessive suffix dual third person +PxPl1 !!= * @CODE@ possessive suffix plural first person +PxPl2 !!= * @CODE@ possessive suffix plural second person +PxPl3 !!= * @CODE@ possessive suffix plural plural person ! Adjectives +Comp !!= * @CODE@ Comparative comparison +Superl !!= * @CODE@ Superlative comparison +Attr !!= * @CODE@ Attribute +Card !!= * @CODE@ +Ord !!≈ * @CODE@ CHECK THIS! In closed-sme there are +Ord entries without circ. tag ! Verbs +Ind !!= * @CODE@ Indicative mood +Prs !!= * @CODE@ Present tense +Prt !!= * @CODE@ Past tense +Pot !!= * @CODE@ Potensial mood +Cond !!= * @CODE@ conditional mood +Imprt !!= * @CODE@ Imperative mood +Sg1 !!= * @CODE@ singular first person +Sg2 !!= * @CODE@ singular second person +Sg3 !!= * @CODE@ singular third person +Du1 !!= * @CODE@ dual first person +Du2 !!= * @CODE@ dual second person +Du3 !!= * @CODE@ dual third person +Pl1 !!= * @CODE@ plural first person +Pl2 !!= * @CODE@ plural second person +Pl3 !!= * @CODE@ plural plural person +Inf !!= * @CODE@ infinitive +Ger !!= * @CODE@ gerundium +ConNeg !!= * @CODE@ the main verb form used with negation verb. Like "bårå" in "Iv bårå guolev" +Neg !!= * @CODE@ negation verb +ImprtII !!= * @CODE@ second imperative mood +PrsPrc !!= * @CODE@ present participle +PrfPrc !!= * @CODE@ past participle +Sup !!= * @CODE@ supinum +VGen !!= * @CODE@ verb genitive +VAbess !!= * @CODE@ verb abessive +Actio !!= * @CODE@ Actio ! Other tags +ABBR !!≈ * @CODE@ +ACR !!≈ * @CODE@ +CLB !!≈ * @CODE@ +PUNCT !!≈ * @CODE@ +LEFT !!≈ * @CODE@ +RIGHT !!≈ * @CODE@ ^GUESSNOUNROOT !!≈ * @CODE@ +TV !!≈ * @CODE@ +IV !!≈ * @CODE@ Transitivity tags +Multi !!≈ * @CODE@ Multiword phrase tag +Guess !!≈ * @CODE@ for the name guesser +NomAg !!≈ * @CODE@ Actor Noun From Verb - Nomen Agentis !! !! !!Lexeme disambiguation tags +Hom1 !!≈ ; @CODE@ : Homonymy +Hom2 !!≈ ; @CODE@ : Homonymy !! !! !!Stem variant tags +v1 !!≈ * @CODE@ - variant 1 +v2 !!≈ * @CODE@ - variant 2 +v3 !!≈ * @CODE@ - variant 3 +v4 !!≈ * @CODE@ - variant 4 +v5 !!≈ * @CODE@ - variant 5 +Cmp/Hyph ! +PAR ! Not in use, it seems. !! !Question and Focus particles: +Qst !!≈ * @CODE@ +Clt !!≈ * @CODE@ +Foc !!≈ * @CODE@ These two are only found in SMJ - do we need them? !! !Focus particles: +Foc/ge !!≈ * @CODE@ +Foc/gen !!≈ * @CODE@ +Foc/ga !!≈ * @CODE@ +Foc/Neg-k !!≈ * @CODE@ +Foc/Pos-k !!≈ * @CODE@ !! !Other tags +MWE !!≈ * @CODE@ multi word expressions, goes to abbr +Sh !!≈ * @CODE@ Short form !! !!Semantic tags to help disambiguation & syntactic analysis !! These tags should always be located just before the POS tag. +Sem/Act !!= * @CODE@ = Activity +Sem/Adr !!= * @CODE@ = Webadr +Sem/Amount !!= * @CODE@ = Amount +Sem/Ani !!= * @CODE@ = Animate +Sem/Aniprod !!= * @CODE@ = Animal Product +Sem/Body !!= * @CODE@ = Bodypart +Sem/Body-abstr !!= * @CODE@ = siellu, vuoig?a, jierbmi +Sem/Build !!= * @CODE@ = Building +Sem/Build-part !!= * @CODE@ = Part of Bulding, like the closet +Sem/Cat !!= * @CODE@ = Category +Sem/Clth !!= * @CODE@ = Clothes +Sem/Clth-jewl !!= * @CODE@ = Jewelery +Sem/Clth-part !!= * @CODE@ = part of clothes, boallu, sávdnji... +Sem/Ctain !!= * @CODE@ = Container +Sem/Ctain-abstr !!= * @CODE@ = Abstract container like bank account +Sem/Ctain-clth !!= * @CODE@ = +Sem/Curr !!= * @CODE@ = Currency like dollár, Not Money +Sem/Dance !!= * @CODE@ = Dance +Sem/Dir !!= * @CODE@ = Direction like GPS-kursa +Sem/Domain !!= * @CODE@ = Domain like politics, reindeerherding (a system of actions) +Sem/Drink !!= * @CODE@ = Drink +Sem/Dummytag !!= * @CODE@ = Dummytag +Sem/Edu !!= * @CODE@ = Educational event +Sem/Event !!= * @CODE@ = Event +Sem/Feat !!= * @CODE@ = Feature, like Árvu +Sem/Feat-phys !!= * @CODE@ = Physiological feature, ivdni, fárda +Sem/Feat-psych !!= * @CODE@ = Psychological feauture +Sem/Feat-measr !!= * @CODE@ = Psychological feauture +Sem/Fem !!= * @CODE@ = Female name +Sem/Food !!= * @CODE@ = Food +Sem/Food-med !!= * @CODE@ = Medicine +Sem/Furn !!= * @CODE@ = Furniture +Sem/Game !!= * @CODE@ = Game +Sem/Geom !!= * @CODE@ = Geometrical object +Sem/Group !!= * @CODE@ = Animal or Human Group +Sem/Hum !!= * @CODE@ = Human +Sem/Hum-abstr !!= * @CODE@ = Human abstract +Sem/Ideol !!= * @CODE@ = Ideology +Sem/Lang !!= * @CODE@ = Language +Sem/Mal !!= * @CODE@ = Male name +Sem/Mat !!= * @CODE@ = Material for producing things +Sem/Measr !!= * @CODE@ = Measure +Sem/Money !!= * @CODE@ = Has to do with money, like wages, not Curr(ency) +Sem/Obj !!= * @CODE@ = Object +Sem/Obj-clo !!= * @CODE@ = Cloth +Sem/Obj-cogn !!= * @CODE@ = Cloth +Sem/Obj-el !!= * @CODE@ = (Electrical) machine or apparatus +Sem/Obj-ling !!= * @CODE@ = Object with something written on it +Sem/Obj-rope !!= * @CODE@ = flexible ropelike object +Sem/Obj-surfc !!= * @CODE@ = Surface object +Sem/Org !!= * @CODE@ = Organisation +Sem/Part !!= * @CODE@ = Feature, oassi, bealli +Sem/Perc-cogn !!= * @CODE@ = Cloth +Sem/Perc-emo !!= * @CODE@ = Emotional perception +Sem/Perc-phys !!= * @CODE@ = Physical perception +Sem/Perc-psych !!= * @CODE@ = Physical perception +Sem/Plant !!= * @CODE@ = Plant +Sem/Plant-part !!= * @CODE@ = Plant part +Sem/Plc !!= * @CODE@ = Place +Sem/Plc-abstr !!= * @CODE@ = Abstract place +Sem/Plc-elevate !!= * @CODE@ = Place +Sem/Plc-line !!= * @CODE@ = Place +Sem/Plc-water !!= * @CODE@ = Place +Sem/Pos !!= * @CODE@ = Position (as in social position job) +Sem/Process !!= * @CODE@ = Process +Sem/Prod !!= * @CODE@ = Product +Sem/Prod-audio !!= * @CODE@ = Audio product +Sem/Prod-cogn !!= * @CODE@ = Cognition product +Sem/Prod-ling !!= * @CODE@ = Linguistic product +Sem/Prod-vis !!= * @CODE@ = Visual product +Sem/Rel !!= * @CODE@ = Relation +Sem/Route !!= * @CODE@ = Route +Sem/Rule !!= * @CODE@ = Rule or convention +Sem/Semcon !!= * @CODE@ = Semantic concept +Sem/Sign !!= * @CODE@ = Sign (e.g. numbers, punctuation) +Sem/Sport !!= * @CODE@ = Sport +Sem/State !!= * @CODE@ = +Sem/State-sick !!= * @CODE@ = Illness +Sem/Substnc !!= * @CODE@ = Substance, like Air and Water +Sem/Sur !!= * @CODE@ = Surname +Sem/Symbol !!= * @CODE@ = Symbol +Sem/Time !!= * @CODE@ = Time +Sem/Tool !!= * @CODE@ = Prototypical tool for repairing things +Sem/Tool-catch !!= * @CODE@ = Tool used for catching (e.g. fish) +Sem/Tool-clean !!= * @CODE@ = Tool used for cleaning +Sem/Tool-it !!= * @CODE@ = Tool used in IT +Sem/Tool-measr !!= * @CODE@ = Tool used for measuring +Sem/Tool-music !!= * @CODE@ = Music instrument +Sem/Tool-write !!= * @CODE@ = Writing tool +Sem/Txt !!= * @CODE@ = Text (girji, lávlla...) +Sem/Veh !!= * @CODE@ = Vehicle +Sem/Wpn !!= * @CODE@ = Weapon +Sem/Wthr !!= * @CODE@ = The Weather or the state of ground !! !Multiple Semantic tags: +Sem/Act_Group !!≈ * @CODE@ Activity and Group +Sem/Act_Plc !!≈ * @CODE@ A persons job is an activity, and a place as well +Sem/Act_Route !!≈ * @CODE@ Activity and Route, ie johtolat +Sem/Amount_Build !!≈ * @CODE@ Amount and Building +Sem/Amount_Semcon !!≈ * @CODE@ +Sem/Ani_Body-abstr_Hum !!≈ * @CODE@ +Sem/Ani_Build !!≈ * @CODE@ +Sem/Ani_Build-part !!≈ * @CODE@ +Sem/Ani_Build_Hum_Txt !!≈ * @CODE@ +Sem/Ani_Group !!≈ * @CODE@ +Sem/Ani_Group_Hum !!≈ * @CODE@ +Sem/Ani_Hum !!≈ * @CODE@ +Sem/Ani_Hum_Plc !!≈ * @CODE@ +Sem/Ani_Hum_Time !!≈ * @CODE@ +Sem/Ani_Plc !!≈ * @CODE@ +Sem/Ani_Plc_Txt !!≈ * @CODE@ +Sem/Ani_Time !!≈ * @CODE@ +Sem/Ani_Veh !!≈ * @CODE@ +Sem/Aniprod_Hum !!≈ * @CODE@ +Sem/Aniprod_Obj-clo !!≈ * @CODE@ +Sem/Aniprod_Perc-phys !!≈ * @CODE@ +Sem/Aniprod_Plc !!≈ * @CODE@ +Sem/Body-abstr_Prod-audio_Semcon !!≈ * @CODE@ +Sem/Body_Body-abstr !!≈ * @CODE@ +Sem/Body_Clth !!≈ * @CODE@ +Sem/Body_Food !!≈ * @CODE@ +Sem/Body_Group_Hum !!≈ * @CODE@ +Sem/Body_Group_Hum_Time !!≈ * @CODE@ +Sem/Body_Hum !!≈ * @CODE@ +Sem/Body_Mat !!≈ * @CODE@ +Sem/Body_Measr !!≈ * @CODE@ +Sem/Body_Obj_Tool-catch !!≈ * @CODE@ +Sem/Body_Plc !!≈ * @CODE@ +Sem/Body_Time !!≈ * @CODE@ +Sem/Build-part_Plc !!≈ * @CODE@ +Sem/Build_Build-part !!≈ * @CODE@ +Sem/Build_Clth-part !!≈ * @CODE@ +Sem/Build_Edu_Org !!≈ * @CODE@ +Sem/Build_Event_Org !!≈ * @CODE@ +Sem/Build_Obj !!≈ * @CODE@ +Sem/Build_Org !!≈ * @CODE@ +Sem/Build_Route !!≈ * @CODE@ +Sem/Clth-jewl_Curr !!≈ * @CODE@ +Sem/Clth-jewl_Money !!≈ * @CODE@ +Sem/Clth-jewl_Plant !!≈ * @CODE@ +Sem/Clth_Hum !!≈ * @CODE@ +Sem/Ctain-abstr_Org !!≈ * @CODE@ +Sem/Ctain-clth_Plant !!≈ * @CODE@ +Sem/Ctain-clth_Veh !!≈ * @CODE@ +Sem/Ctain_Feat-phys !!≈ * @CODE@ +Sem/Ctain_Furn !!≈ * @CODE@ +Sem/Ctain_Plc !!≈ * @CODE@ +Sem/Ctain_Tool !!≈ * @CODE@ +Sem/Ctain_Tool-measr !!≈ * @CODE@ +Sem/Curr_Org !!≈ * @CODE@ +Sem/Dance_Org !!≈ * @CODE@ +Sem/Dance_Prod-audio !!≈ * @CODE@ +Sem/Domain_Food-med !!≈ * @CODE@ +Sem/Domain_Prod-audio !!≈ * @CODE@ +Sem/Edu_Event !!≈ * @CODE@ +Sem/Edu_Group_Hum !!≈ * @CODE@ +Sem/Edu_Mat !!≈ * @CODE@ +Sem/Edu_Org !!≈ * @CODE@ +Sem/Event_Food !!≈ * @CODE@ +Sem/Event_Hum !!≈ * @CODE@ +Sem/Event_Plc !!≈ * @CODE@ +Sem/Event_Plc-elevate !!≈ * @CODE@ +Sem/Event_Time !!≈ * @CODE@ +Sem/Feat-measr_Plc !!≈ * @CODE@ +Sem/Feat-phys_Tool-write !!≈ * @CODE@ +Sem/Feat-phys_Veh !!≈ * @CODE@ +Sem/Feat-phys_Wthr !!≈ * @CODE@ +Sem/Feat-psych_Hum !!≈ * @CODE@ +Sem/Feat_Plant !!≈ * @CODE@ +Sem/Food_Perc-phys !!≈ * @CODE@ +Sem/Food_Plant !!≈ * @CODE@ +Sem/Game_Obj-play !!≈ * @CODE@ +Sem/Geom_Obj !!≈ * @CODE@ +Sem/Group_Hum !!≈ * @CODE@ +Sem/Group_Hum_Org !!≈ * @CODE@ +Sem/Group_Hum_Plc !!≈ * @CODE@ +Sem/Group_Hum_Prod-vis !!≈ * @CODE@ +Sem/Group_Org !!≈ * @CODE@ +Sem/Group_Sign !!≈ * @CODE@ +Sem/Group_Txt !!≈ * @CODE@ +Sem/Hum_Lang !!≈ * @CODE@ +Sem/Hum_Lang_Plc !!≈ * @CODE@ +Sem/Hum_Lang_Time !!≈ * @CODE@ +Sem/Hum_Obj !!≈ * @CODE@ +Sem/Hum_Org !!≈ * @CODE@ +Sem/Hum_Plant !!≈ * @CODE@ +Sem/Hum_Plc !!≈ * @CODE@ +Sem/Hum_Tool !!≈ * @CODE@ +Sem/Hum_Veh !!≈ * @CODE@ +Sem/Hum_Wthr !!≈ * @CODE@ +Sem/Lang_Tool !!≈ * @CODE@ +Sem/Mat_Plant !!≈ * @CODE@ +Sem/Mat_Txt !!≈ * @CODE@ +Sem/Measr_Sign !!= * @CODE@ = Sign (e.g. numbers, punctuation) +Sem/Measr_Time !!≈ * @CODE@ +Sem/Money_Obj !!≈ * @CODE@ +Sem/Money_Txt !!≈ * @CODE@ +Sem/Obj-play !!≈ * @CODE@ +Sem/Obj-play_Sport !!≈ * @CODE@ +Sem/Obj_Semcon !!≈ * @CODE@ +Sem/Clth-jewl_Org !!≈ * @CODE@ +Sem/Org_Rule !!≈ * @CODE@ +Sem/Org_Txt !!≈ * @CODE@ +Sem/Org_Veh !!≈ * @CODE@ +Sem/Part_Prod-cogn !!≈ * @CODE@ +Sem/Part_Substnc !!≈ * @CODE@ +Sem/Perc-emo_Wthr !!≈ * @CODE@ +Sem/Plant_Plant-part !!≈ * @CODE@ +Sem/Plant_Tool !!≈ * @CODE@ +Sem/Plant_Tool-measr !!≈ * @CODE@ +Sem/Plc-abstr_Rel_State !!≈ * @CODE@ +Sem/Plc-abstr_Route !!≈ * @CODE@ +Sem/Plc_Pos !!≈ * @CODE@ +Sem/Plc_Route !!≈ * @CODE@ +Sem/Plc_State !!≈ * @CODE@ +Sem/Plc_Substnc !!≈ * @CODE@ +Sem/Plc_Substnc_Wthr !!≈ * @CODE@ +Sem/Plc_Time !!≈ * @CODE@ +Sem/Plc_Tool-catch !!≈ * @CODE@ +Sem/Plc_Wthr !!≈ * @CODE@ +Sem/Prod-audio_Txt !!≈ * @CODE@ +Sem/Prod-cogn_Txt !!≈ * @CODE@ +Sem/Semcon_Txt !!≈ * @CODE@ +Sem/Obj_State !!≈ * @CODE@ +Sem/Substnc_Wthr !!≈ * @CODE@ +Sem/Time_Wthr !!≈ * @CODE@ +Sem/State-sick_Substnc !!≈ * @CODE@ +Sem/Org_Prod-cogn !!≈ * @CODE@ !! !!Derivation tags !! The following tags are used to describe the dynamic derivational system in !! Lule Sámi as encoded in this lexical description. The tags are classified !! according to a positional system, where each tag can be in one and only one !! position, and can only combine with tags from an earlier / lower position. !! This is done to avoid possible overgeneration in the derivational system. ! Der#begin ! Derivation position in a derivation row: Affix and: ! 1 2 3 4 5 POS type +Der1 +Der2 +Der3 +Der4 +Der5 !!≈ ;@CODE@: - positional tags, preceeds the actual der tag !! !Der#1 tags - tags in first position +Der/PassL !!≈ * @CODE@ VV - long passive láhpeduvvat +Der/PassS !!≈ * @CODE@ VV - Short passive láhpput +Der/PassD !!≈ * @CODE@ VV - dallat passive +Der/Dimin !!≈ * @CODE@ NN +Der/adda !!≈ * @CODE@ VV +Der/ahtja !!≈ * @CODE@ VV - only odd syll verbs take this der +Der/ahttjá !!≈ * @CODE@ VV - only odd syll verbs take this der +Der/Caus !!≈ * @CODE@ VV - previously Der/ahtte +Der/alla !!≈ * @CODE@ VV +Der/asste !!≈ * @CODE@ VV +Der/d !!≈ * @CODE@ VV +Der/dalla !!≈ * @CODE@ VV +Der/dasste !!≈ * @CODE@ VV +Der/Car !!≈ * @CODE@ NA - only even/contr, prev. Der/dibme !+Der/dávtak ! NA Adjectival -k der (from ?). lexicalized +Der/ferjak !!≈ * @CODE@ NA Adjectival -k der (from ?) +Der/k !!≈ * @CODE@ NN / NA +Der/l !!≈ * @CODE@ VV +Der/ladda !!≈ * @CODE@ VV +Der/lahtte !!≈ * @CODE@ VV +Der/lasj !!≈ * @CODE@ NA - dont know, guess it Tronds, ojes, I see - is this ok?jes 2 Der:lasj Noun on 1472 Adj on 2040 +Der/lasj !!≈ * @CODE@ NN +Der/lasste !!≈ * @CODE@ VV +Der/n !!≈ * @CODE@ NA. Denominal -n adjective (similar t -k adj) +Der/r !!≈ * @CODE@ VN - AA? +Der/rávak ! NA Adj. -k der from? +Der/sasj !!≈ * @CODE@ NA +Der/segak !!≈ * @CODE@ NA Adj. -k der from? +Der/st !!≈ * @CODE@ VV +Der/stahtte !!≈ * @CODE@ VV +Der/stalla !!≈ * @CODE@ VV +Der/stasste !!≈ * @CODE@ VV !+Der/stával ! * @CODE@ -l derivation, deverbal? +Der/tj !!≈ * @CODE@ VV +Der/u/a/åd !!≈ * @CODE@ VV !! !Der#2 tags - tags in second position +Der/dahtte !!≈ * @CODE@ VV +Der/duhtte !!≈ * @CODE@ VV +Der/ahkes !!≈ * @CODE@ VA +Der/NomAct !!≈ * @CODE@ VN !! !Der#3 tags - tags in third position +Der/duvva !!≈ * @CODE@ VV +Der/InchL !!≈ * @CODE@ VV (previosuly Der/goahte) +Der/mus !!≈ * @CODE@ VN +Der/NomAct !!≈ * @CODE@ VN Realised in two different ways. !!≈ * @CODE@ This realisation is Der3. Outcommented !!≈ * @CODE@ to not define the tag twice, but kept !!≈ * @CODE@ here for documentation purposes. +Der/dahka !!≈ * @CODE@ VN +Der/lis !!≈ * @CODE@ VA +Der/NomAg !!≈ * @CODE@ VN !! !Der#4 tags - tags in fourth position +Der/ahtes !!≈ * @CODE@ NA ! only odd !! !Der#5 tags - tags in fifth position +Der/AAdv !!≈ * @CODE@ NA AAdv, previously +Der/at +Der/vuota !!≈ * @CODE@ NA AN (tag harmonization: previosuly Der/vuohta) !! !Der#other tags - tags that can be in any position !! There are no such tags in SMJ, but for symmetry and code coherence with SME !! the class is still kept. ! All non-positional derivations should be preceded by this tag, to make it possible ! to target regular expressions at all derivations in a language-independent way: ! just specify [+Der|+Der1 .. +Der5] and you are set. +Der ! Der#end !! !!Tags for originating language !! !! The following tags are used to guide conversion to IPA: loan words !! and foreign names are usually pronounced (approximately) as in the !! originating (majority) language. Instead of trying to identify the !! correct pronounciation based on fonotactics (orthotactics actually), !! we tag all words that can't be correctly transcribed using the SME !! transcriber with source language codes. Once tagged, it is possible !! to split the lexical transducer in smaller ones according to langu- !! age, and apply different IPA conversion to each of them. !! !! The principle of tagging is that we only tag to the extent needed, !! and following a priority: !! # any untagged word is pronounced with SME orthographic conventions !! # NNO and NOB have identical pronounciation, NNO is only used if !! different in spelling from NOB !! # SWE has mostly the same pronounciation as NOB, and is only used !! if different in spelling from NOB !! # Occasionally even SME (the default) may be tagged, to block other !! languages from being specified, mainly during semi-automatic !! language tagging sessions !! !! All in all, we want to get as much correctly transcribed to IPA !! with as little work as possible. On the other hand, if more words !! are tagged than strictly needed, this should pose no problem as !! long as the IPA conversion is correct - at least some words will !! get the same pronounciation whether read as SME or NOB/NNO/SWE. !! +OLang/SME !!≈ * @CODE@ - North Sámi +OLang/SMA !!≈ * @CODE@ - South Sámi +OLang/FIN !!≈ * @CODE@ - Finnish +OLang/SWE !!≈ * @CODE@ - Swedish +OLang/NOB !!≈ * @CODE@ - Norw. bokmål +OLang/NNO !!≈ * @CODE@ - Norw. nynorsk +OLang/ENG !!≈ * @CODE@ - English +OLang/RUS !!≈ * @CODE@ - Russian +OLang/UND !!≈ * @CODE@ - Undefined ! Morphophonemes and Sámi letters ! e7 e9 i7 o7 o9 u7 ! Morphophonemes in sme, here temporarily due to common propernoun file ! g8 m8 n8 h8 ! b9 d9 g9 h9 l9 m9 n9 r9 ! k9 t9 ! From sme-lex.txt ! Morphophonemes and Sámi letters a9 b9 e7 e9 d9 g8 g9 h8 h9 i7 j9 k9 l9 m8 m9 n8 n9 o7 o9 p9 r9 s9 t9 u7 z9 æ9 ä9 '7 r9 ø9 ö9 ! A9 B9 E7 E9 D9 G8 G9 H8 H9 I7 J9 K9 M8 M9 N8 N9 O7 O9 P9 ! S9 T9 U7 Z9 Æ9 Ä9 R9 Ø9 Ö9 ! Symbols that need to be escaped on the lower side (towards twolc): »7 ! » «7 ! « %[%>%] ! > %[%<%] ! < ! Triggers for morphophonological rules X1 X2 X3 X4 X5 X6 X7 X8 X9 Q1 Q2 Q3 Q4 Q5 Q6 Q7 Q8 Q9 Y1 Y2 Y3 Y4 Y5 Y6 Y7 Y8 Y9 Z1 !! !!Flag diacritics !! We have manually optimised the structure of our lexicon using following !! flag diacritics to restrict morhpological combinatorics - only allow compounds !! with verbs if the verb is further derived into a noun again: @P.NeedNoun.ON@ !!≈ | @CODE@ | (Dis)allow compounds with verbs unless nominalised @D.NeedNoun.ON@ !!≈ | @CODE@ | (Dis)allow compounds with verbs unless nominalised @C.NeedNoun@ !!≈ | @CODE@ | (Dis)allow compounds with verbs unless nominalised !! !! For languages that allow compounding, the following flag diacritics are needed !! to control position-based compounding restrictions for nominals. Their use is !! handled automatically if combined with +CmpN/xxx tags. If not used, they will !! do no harm. @P.CmpFrst.FALSE@ !!≈ | @CODE@ | Require that words tagged as such only appear first @D.CmpPref.TRUE@ !!≈ | @CODE@ | Block such words from entering ENDLEX @P.CmpPref.FALSE@ !!≈ | @CODE@ | Block these words from making further compounds @D.CmpLast.TRUE@ !!≈ | @CODE@ | Block such words from entering R @D.CmpNone.TRUE@ !!≈ | @CODE@ | Combines with the next tag to prohibit compounding @U.CmpNone.FALSE@ !!≈ | @CODE@ | Combines with the prev tag to prohibit compounding @U.CmpNone.TRUE@ !!≈ | @CODE@ | Combines with the two previous ones to block compounding @P.CmpOnly.TRUE@ !!≈ | @CODE@ | Sets a flag to indicate that the word has passed R @D.CmpOnly.FALSE@ !!≈ | @CODE@ | Disallow words coming directly from root. @U.CmpHyph.FALSE@ !!≈ | @CODE@ | Flag to control hyphenated compounds like proper nouns @U.CmpHyph.TRUE@ !!≈ | @CODE@ | Flag to control hyphenated compounds like proper nouns @C.CmpHyph@ !!≈ | @CODE@ | Flag to control hyphenated compounds like proper nouns !! !! Use the following flag diacritics to control downcasing of derived proper !! nouns (e.g. Finnish Pariisi -> pariisilainen). See e.g. North Sámi for how to use !! these flags. There exists a ready-made regex that will do the actual down-casing !! given the proper use of these flags. @U.Cap.Obl@ !!≈ | @CODE@ | Allowing downcasing of derived names: deatnulasj. @U.Cap.Opt@ !!≈ | @CODE@ | Allowing downcasing of derived names: deatnulasj. @P.Px.add@ !!≈ | @CODE@ | Giving possibility for Px-suffixes (all except from Nom 3.p) @R.Px.add@ !!≈ | @CODE@ | Requiring P.Px.add-flag for Px-suffixes (all except from Nom 3.p) @P.Nom3Px.add@ !!≈ | @CODE@ | Giving possibility for Px-suffixes Nom 3.p @R.Nom3Px.add@ !!≈ | @CODE@ | Requiring P.Nom3Px.add flag for Px-suffixes Nom 3.p ! ================================================= ! Basic lexica, pointing to the other lexicon files ! ================================================= LEXICON Root @U.Cap.Obl@ ProperNoun ; @U.Cap.Opt@ ProperNoun ; Prefixes ; NounRoot ; ! ProperNounFirstPart ; Adjective ; Verb ; Adverb ; Particle ; Subjunction ; Conjunction ; Adposition ; ! Postposition ; ! Preposition ; Interjection ; Pronoun ; +Use/CircN: Numeral ; Acronym ; Abbreviation ; Punctuation ; LEXICON ProperNoun !!= * __@CODE@__ @U.CmpHyph.TRUE@ ProperNoun-smj-nocomp ; ! Lexicon for SMJ short names - always require hyphen @U.CmpHyph.TRUE@ ProperNoun-smi-nocomp ; ! Lexicon for short names - always require hyphen ProperNoun-smi ; ! SMI proper nouns ProperNoun-smj ; ! contains the full smj name list FirstComponentProper ; ! Short forms LEXICON ENDLEX !! !!!Lexicon @LEXNAME@ !! And this is the @LEXNAME@ of everything: !! {{{ @D.CmpOnly.FALSE@@D.CmpPref.TRUE@@D.NeedNoun.ON@ # ; !!≈ @CODE@ !! }}} !! The {{@D.CmpOnly.FALSE@}} flag diacritic is ued to disallow words tagged !! with +CmpNP/Only to end here. !! The {{@D.NeedNoun.ON@}} flag diacritic is used to block illegal compounds.