instance DiffUrd of DiffHindustani = open CommonHindustani, Prelude in { flags coding = utf8 ; oper Clause : Type = {s : VPHTense => Polarity => Order => Str} ; mkClause : NP -> VPH -> Clause = \np,vp -> { s = \\vt,b,ord => let subjagr : NPCase * Agr = case vt of { VPImpPast => case vp.subj of { VTrans => ; VTransPost => ; _ => } ; _ => } ; subj = subjagr.p1 ; agr = subjagr.p2 ; n = (fromAgr agr).n; p = (fromAgr agr).p; g = (fromAgr agr).g; vps = case vt of { VPGenPres => vp.s ! VPTense VPPres agr ; VPImpPast => vp.s ! VPTense VPPast agr ; VPFut => case vp.prog of { True => {fin = (vp.s ! VPTense VPFutr agr).fin ; inf = (vp.s ! VPTense VPFutr agr).inf ++ hw p n} ; _ => vp.s ! VPTense VPFutr agr } ; VPContPres => {fin = copula CPresent n p g ; inf = (vp.s ! VPStem).inf ++ raha g n } ; VPContPast => {fin = copula CPast n p g ; inf = (vp.s ! VPStem).inf ++ raha g n } ; VPContFut => {fin = copula CFuture n p g ; inf = (vp.s ! VPStem).inf ++ raha g n ++ hw p n} ; VPPerfPres => {fin = copula CPresent n p g ; inf = (vp.s ! VPTense VPPerf agr).inf } ; VPPerfPast => {fin = copula CPast n p g ; inf = (vp.s ! VPTense VPPerf agr).inf } ; VPPerfFut => {fin = copula CFuture n p g ; inf = (vp.s ! VPTense VPPerf agr).inf ++ hw p n } ; VPPerfPresCont => {fin = copula CPresent n p g ; inf = (vp.s ! VPTense VPPres agr).inf ++ raha g n } ; VPPerfPastCont => {fin = copula CPast n p g ; inf = (vp.s ! VPTense VPPres agr).inf ++ raha g n } ; VPPerfFutCont => {fin = copula CFuture n p g ; inf = (vp.s ! VPTense VPPres agr).inf ++ raha g n ++ hw p n } ; VPSubj => case vp.prog of { True => {fin = (vp.s ! VPTense VPFutr agr).inf ++ hw p n ; inf = "Xayd" } ; _ => {fin = (vp.s ! VPTense VPFutr agr).inf ; inf = "Xayd" } } }; quest = case ord of { ODir => []; OQuest => "kya" }; na = case b of { Pos => []; Neg => "na" }; nahim = case b of { Pos => []; Neg => "nhyN" }; in case vt of { VPSubj => quest ++ np.s ! subj ++ vp.obj.s ++ vp.ad ++ vp.comp ! np.a ++ na ++ vps.inf ++ vps.fin ++ vp.embComp ; _ => quest ++ np.s ! subj ++ vp.obj.s ++ vp.ad ++ vp.comp ! np.a ++ nahim ++ vps.inf ++ vps.fin ++ vp.embComp}; } ; mkSClause : Str -> Agr -> VPH -> Clause = \subj,agr,vp -> { s = \\t,b,ord => let n = (fromAgr agr).n; p = (fromAgr agr).p; g = (fromAgr agr).g; vps = case t of { VPGenPres => vp.s ! VPTense VPPres agr ; VPImpPast => vp.s ! VPTense VPPast agr ; VPFut => vp.s ! VPTense VPFutr agr ; VPContPres => {fin = copula CPresent n p g ; inf = (vp.s ! VPStem).inf ++ raha g n } ; VPContPast => {fin = copula CPast n p g ; inf = (vp.s ! VPStem).inf ++ raha g n } ; VPContFut => {fin = copula CFuture n p g ; inf = (vp.s ! VPStem).inf ++ raha g n ++ hw p n } ; VPPerfPres => {fin = copula CPresent n p g ; inf = (vp.s ! VPStem).inf ++ cka g n } ; VPPerfPast => {fin = copula CPast n p g ; inf = (vp.s ! VPStem).inf ++ cka g n } ; VPPerfFut => {fin = copula CFuture n p g ; inf = (vp.s ! VPStem).inf ++ cka g n ++ hw p n } ; VPPerfPresCont => {fin = copula CPresent n p g ; inf = (vp.s ! VPStem).inf ++ raha g n } ; VPPerfPastCont => {fin = copula CPast n p g ; inf = (vp.s ! VPStem).inf ++ raha g n } ; VPPerfFutCont => {fin = copula CFuture n p g ; inf = (vp.s ! VPStem).inf ++ raha g n ++ hw p n } ; VPSubj => {fin = insertSubj p (vp.s ! VPStem).inf ; inf = "Xayd" } }; quest = case ord of { ODir => []; OQuest => "kya" }; na = case b of { Pos => []; Neg => "na" }; nahim = case b of { Pos => []; Neg => "nhyN" }; in case t of { VPSubj => quest ++ subj ++ vp.obj.s ++ vp.ad ++ vp.comp ! agr ++ na ++ vps.inf ++ vps.fin ++ vp.embComp; _ => quest ++ subj ++ vp.obj.s ++ vp.ad ++ vp.comp ! agr ++ nahim ++ vps.inf ++ vps.fin ++ vp.embComp}; } ; np2pronCase ppf npc a = case npc of { NPC c => ppf ! c; NPObj => ppf ! Obl ; NPErg => case (fromAgr a).p of { (Pers3_Near|Pers3_Distant) => ppf ! Obl ++ "nE" ; _ => ppf ! Dir ++ "nE" } } ; conjThat = "kh" ; insertSubj : UPerson -> Str -> Str = \p,s -> case p of { Pers1 => s ++ "waN" ; _ => s ++ "E"}; -- check with prasad for vn~ agr = "agr" ; awr = "awr" ; ky = "ky" ; jn = "jn" ; js = "js" ; jw = "jw" ; kw = "kw" ; mt = "mt" ; nE = "nE" ; nh = "na" ; sE = "sE" ; waN = "waN" ; hE = "hE" ; comma = "," ; indfArt = "ak" ; kwd = "Kwd" ; copula : CTense -> Number -> UPerson -> Gender -> Str = \t,n,p,g -> case of { => "hwN" ; => "hE"; => "hw" ; => "hyN" ; => "hE" ; => "hE" ; => "hyN" ; => "hw" ; => "hw" ; => "hyN" ; => "hyN" ; => "hyN" ; => "th'a" ; => "th'y" ; => "th'a" ; => "th'y" ; => "th-a" ; => "th'y" ; => "th'E" ; => "th'yN" ; => "th-a" ; => "th'y" ; => "th-a" ; => "th'y" ; => "th'E" ; => "th'yN" ; => "th'E" ; => "th'yN" ; => "th'E" ; => "th'yN" ; => "th'E" ; => "th'yN" ; => "th'E" ; => "th'yN" ; => "th'E" ; => "th'yN" ; => "ga" ; => "gy" ; => "ga" ; => "gy" ; => "gE" ; => "gy" ; => "gE" ; => "gy" ; => "ga" ; => "gy" ; => "ga" ; => "gy" ; => "gE" ; => "gy" ; => "gE" ; => "gy" ; => "gE" ; => "gy" ; => "gE" ; => "gy" ; => "gE" ; => "gE" ; => "gE" ; => "gy" } ; raha : Gender -> Number -> Str = \g,n -> (regAdjective "rha").s ! n ! g ! Dir ! Posit ; cka : Gender -> Number -> Str = \g,n -> (regAdjective "cka").s ! n ! g ! Dir ! Posit ; hw : UPerson -> Number -> Str = \pp,n -> case of { => "hwN"; <_,Pl> => "hwN"; <_,_> => "hw" }; hwa : Agr -> Str = \agr -> let n = (fromAgr agr).n; p = (fromAgr agr).p; g = (fromAgr agr).g; in case of { => "hwa"; => "hwy"; => "hwE" ; => "hwy" }; ----------------------------------------------- -- Hindustani Adjectives ----------------------------------------------- Adjective = { s: Number => Gender => Case => Degree => Str }; regAdjective : Str -> Adjective; regAdjective x = case x of { acch + ("a"|"aN") => mkAdjective x ("bht" ++ x) ("sb sE" ++ x) (acch + "E") ("bht" ++ acch + "E") ("sb sE" ++ acch + "E") (acch + "E") ("bht" ++ acch + "E") ("sb sE" ++ acch + "E") (acch + "y") ("bht" ++ acch + "y") ("sb sE" ++ acch + "y") (acch + "y") ("bht" ++ acch + "y") ("sb sE" ++ acch + "y") (acch + "y") ("bht" ++ acch + "y") ("sb sE" ++ acch + "y") (acch +"E") ("bht" ++ acch + "E") ("sb sE" ++ acch + "E") (acch + "E") ("bht" ++ acch + "E") ("sb sE" ++ acch + "E") (acch + "E") ("bht" ++ acch + "E") ("sb sE" ++ acch + "E") (acch + "y") ("bht" ++ acch + "y") ("sb sE" ++ acch + "y") (acch + "y") ("bht" ++ acch + "y") ("sb sE" ++ acch + "y") (acch + "y") ("bht" ++ acch + "y") ("sb sE" ++ acch + "y"); _ => mkAdjective x ("bht" ++ x) ("sb sE" ++ x) x ("bht" ++ x) ("sb sE" ++ x) x ("bht" ++ x) ("sb sE" ++ x) x ("bht" ++ x) ("sb sE" ++ x) x ("bht" ++ x) ("sb sE" ++ x) x ("bht" ++ x) ("sb sE" ++ x) x ("bht" ++ x) ("sb sE" ++ x) x ("bht" ++ x) ("sb sE" ++ x) x ("bht" ++ x) ("sb sE" ++ x) x ("bht" ++ x) ("sb sE" ++ x) x ("bht" ++ x) ("sb sE" ++ x) x ("bht" ++ x) ("sb sE" ++ x) }; }