--# -path=.:../../prelude -- ----1 A Simple Punjabi Resource Morphology ---- ---- Shafqat Virk, Aarne Ranta,2010 ---- ---- This resource morphology contains definitions needed in the resource ---- syntax. To build a lexicon, it is better to use $ParadigmsPnb$, which ---- gives a higher-level access to this module. -- resource MorphoPes = ResPes ** open Prelude,Predef in { flags optimize=all ; coding = utf8; ----2 Nouns oper mkN : (x1,x2 : Str) -> Animacy -> Noun = \sg,pl,ani -> { s = table { bEzafa => table { Sg => sg ; Pl => pl } ; aEzafa => table { Sg => mkEzafa sg ; Pl => mkEzafa pl } ; enClic => table { Sg => mkEnclic sg ; Pl => mkEnclic pl } }; animacy = ani ; definitness = True } ; -- masculine nouns end with alif, choTi_hay, ain Translitration: (a, h, e) -- Arabic nouns ends with h. also taken as Masc ------------------------------------------------------------------ ----Verbs ------------------------------------------------------------------ {- mkVerb : (x1,x2 : Str) -> Verb = \inf,root2 -> let root1 = (tk 1 inf) ; in { s = table { Root1 => root1 ; Root2 => root2 ; Inf => inf ; VF tense aspect person number => (mkCmnVF root1 root2 tense aspect person number).s -- Caus1 tense person number gender => (mkCmnVF root1 tense person number gender).s ; -- Caus2 tense person number gender => (mkCmnVF root2 tense person number gender).s } } ; --1. Basic stem form, direct & indirect causatives exists -- v1 nechna nechaana nechwana mkVerb1 : (_: Str) -> Verb = \inf -> let root1 = (tk 1 inf) ; root2 = (tk 3 inf) ; in { s = table { Root1 => root1 ; Root2 => root2 ; Inf => inf ; VF tense aspect person number => (mkCmnVF root1 root2 tense aspect person number).s -- Caus1 tense person number gender => (mkCmnVF root1 tense person number gender).s ; -- Caus2 tense person number gender => (mkCmnVF root2 tense person number gender).s } } ; mkVerb2 : (_: Str) -> Verb = \inf -> let root1 = (tk 1 inf) ; root2 = (tk 2 inf) ; in { s = table { Root1 => root1 ; Root2 => root2 ; Inf => inf ; VF tense aspect person number => (mkCmnVF root1 root2 tense aspect person number).s -- Caus1 tense person number gender => (mkCmnVF root1 tense person number gender).s ; -- Caus2 tense person number gender => (mkCmnVF root2 tense person number gender).s } } ; mkCmnVF : Str -> Str -> VTense -> PAspect -> PPerson -> Number -> {s:Str}= \root1,root2,t,a,p,n -> {s = (mkCmnVF1 root1 root2 t a p n).s ; }; mkCmnVF1 : Str -> Str -> VTense -> PAspect -> PPerson -> Number -> {s:Str}= \root1,root2,t,a,p,n -> {s = let khordh = root1 + "h"; mekhor = "my" ++ root2 ; mekhord = "my" ++ root1 ; mekhordh = "my" ++ khordh ; khah = "KvAh" ; mekhah = "my" ++ khah ; bvdh = "bvdh" in case of { => khordh ++ "Am" ; => khordh ++ "Aym" ; => khordh ++ "Ay" ; => khordh ++ "Ayd" ; => khordh ++ "Ast" ; => khordh ++ "And" ; => mekhor + "m" ; -- toHave need to have khor instead of mekhor => mekhor + "ym" ; => mekhor + "y" ; => mekhor + "yd" ; => mekhor + "d" ; => mekhor + "nd" ; => "" ; => "" ; => "" ; => "" ; => "" ; => "" ; => khordh ++ "bvdm" ; => khordh ++ "bvdym" ; => khordh ++ "bvdy" ; => khordh ++ "bvdyd" ; => khordh ++ "bvd" ; => khordh ++ "bvdnd" ; => mekhord + "m" ; -- toHave need to have khor instead of mekhor => mekhord + "ym" ; => mekhord + "y"; => mekhord + "yd" ; => mekhord ; => mekhord + "nd" ; => root1 + "m" ; => root1 + "ym" ; => root1 + "y"; => root1 + "yd" ; => root1 ; => root1 + "nd" ; -- check this one => "" ; => "" ; => "" ; => "" ; => "" ; => "" ; => mekhah + "m" ++ addBh root2 + "m" ; => mekhah + "ym" ++ addBh root2 + "ym" ; => mekhah + "y" ++ addBh root2 + "y" ; => mekhah + "yd" ++ addBh root2 + "yd" ; => mekhah + "d" ++ addBh root2 + "d" ; => mekhah + "nd" ++ addBh root2 + "nd" ; => khah + "m" ++ root1 ; => khah + "ym" ++ root1 ; => khah + "y" ++ root1 ; => khah + "yd" ++ root1 ; => khah + "d" ++ root1 ; => khah + "nd" ++ root1 ; => khordh ++ bvdh ++ "Am" ; => khordh ++ bvdh ++ "Aym" ; => khordh ++ bvdh ++ "Ay" ; => khordh ++ bvdh ++ "Ayd" ; => khordh ++ bvdh ++ "Ast" ; => khordh ++ bvdh ++ "And" ; => mekhordh ++ "Am" ; -- toHave need to have khordh instead of mekhor => mekhordh ++ "Aym" ; => mekhordh ++ "Ay" ; => mekhordh ++ "Ayd" ; => mekhordh ++ "Ast" ; => mekhordh ++ "And" ; -- check this one => "" ; => "" ; => "" ; => "" ; => "" ; => "" } } ; -} mkVerb : (x1,x2 : Str) -> Verb = \inf,root2 -> let root1 = (tk 1 inf) ; impRoot = mkimpRoot root2; in { s = table { Root1 => root1 ; Root2 => root2 ; Inf => inf ; Imp Pos Sg => addBh impRoot ; Imp Pos Pl => (addBh impRoot) + "yd" ; Imp Neg Sg => "n" + impRoot ; Imp Neg Pl => "n" + impRoot + "yd" ; VF pol tense person number => (mkCmnVF root1 root2 pol tense person number).s ; -- VF Neg tense person number => addN (mkCmnVF root1 root2 tense person number).s ; Vvform (AgPes number person) => (mkvVform root2 number person).s } } ; mkVerb1 : (_: Str) -> Verb = \inf -> let root1 = (tk 1 inf) ; root2 = (tk 3 inf) ; impRoot = mkimpRoot root2 ; in { s = table { Root1 => root1 ; Root2 => root2 ; Inf => inf ; Imp Pos Sg => addBh impRoot ; Imp Pos Pl => (addBh impRoot) + "yd" ; Imp Neg Sg => "n" + impRoot ; Imp Neg Pl => "n" + impRoot + "yd" ; VF pol tense person number => (mkCmnVF root1 root2 pol tense person number).s ; -- VF Neg tense person number => addN (mkCmnVF root1 root2 tense person number).s ; Vvform (AgPes number person) => (mkvVform root2 number person).s } }; mkVerb2 : (_: Str) -> Verb = \inf -> let root1 = (tk 1 inf) ; root2 = (tk 2 inf) ; impRoot = mkimpRoot root2 ; in { s = table { Root1 => root1 ; Root2 => root2 ; Inf => inf ; Imp Pos Sg => addBh impRoot ; Imp Pos Pl => (addBh impRoot) + "yd" ; Imp Neg Sg => "n" + impRoot ; Imp Neg Pl => "n" + impRoot + "yd" ; VF pol tense person number => (mkCmnVF root1 root2 pol tense person number).s ; -- VF Neg tense person number => addN (mkCmnVF root1 root2 tense person number).s ; Vvform (AgPes number person) => (mkvVform root2 number person).s } } ; mkHave : Verb = { s = table { Root1 => "dACt" ; Root2 => "dAr" ; Inf => "dACtn" ; Imp Pos Sg => ["dACth bAC"] ; Imp Pos Pl => ["dACth bACyd"]; Imp Neg Sg => ["ndACth bAC"] ; Imp Neg Pl => ["ndACth bACyd"] ; VF pol tense person number => (toHave pol tense number person).s ; -- VF Neg tense person number => addN (mkCmnVF root1 root2 tense person number).s ; Vvform (AgPes Sg PPers1) => ["dACth bACm"] ; Vvform (AgPes Sg PPers2) => ["dACth bACy"] ; Vvform (AgPes Sg PPers3) => ["dACth bACd"] ; Vvform (AgPes Pl PPers1) => ["dACth bACym"] ; Vvform (AgPes Pl PPers2) => ["dACth bACyd"] ; Vvform (AgPes Pl PPers3) => ["dACth bACnd"] } } ; mkCmnVF : Str -> Str -> Polarity -> VTense2 -> PPerson -> Number -> {s:Str}= \root1,root2,pol,t,p,n -> {s = (mkCmnVF1 root1 root2 pol t p n).s ; }; mkCmnVF1 : Str -> Str -> Polarity -> VTense2 -> PPerson -> Number -> {s:Str}= \root1,root2,pol,t,p,n -> {s = let khordh = root1 + "h"; nkhordh = (addN root1) + "h" ; mekhor = "my" ++ root2 ; nmekhor = "nmy" ++ root2 ; mekhord = "my" ++ root1 ; nmekhord = "nmy" ++ root1 ; mekhordh = "my" ++ khordh ; nmekhordh = "nmy" ++ khordh ; khah = "KvAh" ; nkhah = "nKvAh" ; mekhah = "my" ++ khah ; nmekhah = "nmy" ++ khah ; bvdh = "bvdh" in case of { => khordh ++ "Am" ; => khordh ++ "Aym" ; => khordh ++ "Ay" ; => khordh ++ "Ayd" ; => khordh ++ "Ast" ; => khordh ++ "And" ; => mekhor + "m" ; => mekhor + "ym" ; => mekhor + "y" ; => mekhor + "yd" ; => mekhor + "d" ; => mekhor + "nd" ; => khordh ++ "bvdm" ; => khordh ++ "bvdym" ; => khordh ++ "bvdy" ; => khordh ++ "bvdyd" ; => khordh ++ "bvd" ; => khordh ++ "bvdnd" ; => mekhord + "m" ; => mekhord + "ym" ; => mekhord + "y"; => mekhord + "yd" ; => mekhord ; => mekhord + "nd" ; => root1 + "m" ; => root1 + "ym" ; => root1 + "y"; => root1 + "yd" ; => root1 ; => root1 + "nd" ; {- => mekhah + "m" ++ addBh root2 + "m" ; => mekhah + "ym" ++ addBh root2 + "ym" ; => mekhah + "y" ++ addBh root2 + "y" ; => mekhah + "yd" ++ addBh root2 + "yd" ; => mekhah + "d" ++ addBh root2 + "d" ; => mekhah + "nd" ++ addBh root2 + "nd" ; -} => khah + "m" ++ root1 ; => khah + "ym" ++ root1 ; => khah + "y" ++ root1 ; => khah + "yd" ++ root1 ; => khah + "d" ++ root1 ; => khah + "nd" ++ root1 ; => khordh ++ bvdh ++ "Am" ; => khordh ++ bvdh ++ "Aym" ; => khordh ++ bvdh ++ "Ay" ; => khordh ++ bvdh ++ "Ayd" ; => khordh ++ bvdh ++ "Ast" ; => khordh ++ bvdh ++ "And" ; => mekhordh ++ "Am" ; => mekhordh ++ "Aym" ; => mekhordh ++ "Ay" ; => mekhordh ++ "Ayd" ; => mekhordh ++ "Ast" ; => mekhordh ++ "And" ; -- negatives => addN khordh ++ "Am" ; => addN khordh ++ "Aym" ; => addN khordh ++ "Ay" ; => addN khordh ++ "Ayd" ; => addN khordh ++ "Ast" ; => addN khordh ++ "And" ; => nmekhor + "m" ; => nmekhor + "ym" ; => nmekhor + "y" ; => nmekhor + "yd" ; => nmekhor + "d" ; => nmekhor + "nd" ; => nkhordh ++ "bvdm" ; => nkhordh ++ "bvdym" ; => nkhordh ++ "bvdy" ; => nkhordh ++ "bvdyd" ; => nkhordh ++ "bvd" ; => nkhordh ++ "bvdnd" ; => nmekhord + "m" ; => nmekhord + "ym" ; => nmekhord + "y"; => nmekhord + "yd" ; => nmekhord ; => nmekhord + "nd" ; => addN root1 + "m" ; => addN root1 + "ym" ; => addN root1 + "y"; => addN root1 + "yd" ; => addN root1 ; => addN root1 + "nd" ; {- => nmekhah + "m" ++ addBh root2 + "m" ; => nmekhah + "ym" ++ addBh root2 + "ym" ; => nmekhah + "y" ++ addBh root2 + "y" ; => nmekhah + "yd" ++ addBh root2 + "yd" ; => nmekhah + "d" ++ addBh root2 + "d" ; => nmekhah + "nd" ++ addBh root2 + "nd" ; -} => nkhah + "m" ++ root1 ; => nkhah + "ym" ++ root1 ; => nkhah + "y" ++ root1 ; => nkhah + "yd" ++ root1 ; => nkhah + "d" ++ root1 ; => nkhah + "nd" ++ root1 ; => nkhordh ++ bvdh ++ "Am" ; => nkhordh ++ bvdh ++ "Aym" ; => nkhordh ++ bvdh ++ "Ay" ; => nkhordh ++ bvdh ++ "Ayd" ; => nkhordh ++ bvdh ++ "Ast" ; => nkhordh ++ bvdh ++ "And" ; => nmekhordh ++ "Am" ; => nmekhordh ++ "Aym" ; => nmekhordh ++ "Ay" ; => nmekhordh ++ "Ayd" ; => nmekhordh ++ "Ast" ; => nmekhordh ++ "And" } } ; mkvVform : Str -> Number -> PPerson -> {s: Str} = \root2,n,p -> {s = case of { => addBh root2 + "m" ; => addBh root2 + "y" ; => addBh root2 + "d" ; => addBh root2 + "ym" ; => addBh root2 + "yd" ; => addBh root2 + "nd" } }; mkimpRoot : Str -> Str ; mkimpRoot root = case root of { st + "y" => st ; _ => root }; addBh : Str -> Str ; addBh str = case (take 1 str) of { "A" => "by" + str ; "A:" => "byA" + (drop 1 str) ; _ => "b" + str }; --------------------- --Determiners -------------------- makeDet : Str -> Number -> Bool -> {s: Str ; n : Number ; isNum : Bool ; fromPron : Bool} =\str,n,b -> { s = str; isNum = b; fromPron = False ; n = n }; makeQuant : Str -> Str -> {s : Number => Str ; a : AgrPes ; fromPron : Bool } = \sg,pl -> { s = table {Sg => sg ; Pl => pl} ; fromPron = False ; a = agrPesP3 Sg }; --------------------------- -- Adjectives -------------------------- mkAdj : Str -> Str -> Adjective = \adj,adv -> { s = table { bEzafa => adj; aEzafa => mkEzafa adj ; enClic => mkEnclic adj } ; adv = adv }; }