--# -path=.:../romance:../abstract:../common:prelude instance DiffCat of DiffRomance - [partAgr,vpAgrSubj,vpAgrClits] = open CommonRomance, PhonoCat, BeschCat, Prelude in { flags optimize=noexpand ; coding=utf8 ; ---- exceptions ---------------- oper partAgr : VType -> Bool = \vtyp -> False ; vpAgrSubj : Verb -> VPAgrType = \v -> ; vpAgrClits : Verb -> AAgr -> VPAgrType = \v,a -> ; -------------------------------- param Prepos = P_de | P_a ; VType = VHabere | VRefl ; oper dative : Case = CPrep P_a ; genitive : Case = CPrep P_de ; prepCase = \c -> case c of { Nom => [] ; Acc => [] ; CPrep P_de => elisDe ; CPrep P_a => "a" } ; artDef : Bool -> Gender -> Number -> Case -> Str = \isNP,g,n,c -> case of { ---- TODO: check the NP forms => pre {"del" ; ("de l'" ++ Predef.BIND) / vocalForta} ; => pre {"al" ; ("a l'" ++ Predef.BIND) / vocalForta} ; => elisEl ; => prepCase c ++ elisLa ; => "dels" ; => ["de les"] ; => "als" ; => ["a les"] ; => "els" ; => "les" } ; artIndef = \isNP,g,n,c -> case isNP of { True => case of { => genForms ("d' ++ Predef.BIND ++ un") ("d' ++ Predef.BIND ++ una") ! g ; => prepCase c ++ genForms "un" "una" ! g ; => genForms ("d' ++ Predef.BIND ++ uns") ("d' ++ Predef.BIND ++ unes") ! g ; -- AR 3/12/2014 => prepCase c ++ genForms "uns" "unes" ! g } ; _ => case of { => genForms ("d' ++ Predef.BIND ++ un") ("d' ++ Predef.BIND ++ una") ! g ; => prepCase c ++ genForms "un" "una" ! g ; => prepCase c --- ++ genForms "uns" "unes" ! g --- take this as a determiner } } ; possCase = \_,_,c -> prepCase c ; partitive = \g,c -> case c of { CPrep P_de => "de" ; _ => prepCase c ++ artDef False g Sg (CPrep P_de) } ; conjunctCase : Case -> Case = \c -> case c of { Nom => Nom ; _ => Acc } ; auxVerb : VType -> (VF => Str) = \_ -> haver_V.s ; vpAgrClit : Agr -> VPAgr = \a -> vpAgrNone ; pronArg = \n,p,acc,dat -> let paccp = case acc of { CRefl => ; CPron ag an ap => ; _ => <[],P2,False> } ; pdatp = case dat of { CPron ag an ap => ; _ => <[],P2,False> } in case of { ---- AR 8/6/2008 efficiency problem in pgf generation: ---- replace the case expr with ---- a constant produces an error in V3 predication with two pronouns ---- => <"se" ++ paccp.p1, [],True> ; _ => } ; --case of { -- => <"te" ++ "me", []> ; -- <_,_,CPron {n = Sg ; p = P2},CPron {n = Sg ; p = P1}> => <"te" ++ "me", []> ; infForm _ _ _ _ = True ; mkImperative b p vp = \\pol,g,n => let pe = case b of {True => P3 ; _ => p} ; agr = {g = g ; n = n ; p = pe} ; refl = case vp.s.vtyp of { VRefl => ; _ => <[],False> } ; clpr = ; ---- TODO: True if clit ---- clpr = <[],[],False> ; ----e pronArg agr.n agr.p vp.clAcc vp.clDat ; ----e verb = case of { ----e => (vp.s ! VPInfinit Simul clpr.p3).inf ! aag ; ----e _ => (vp.s ! VPImperat).fin ! agr ----e } ; verb = vp.s.s ! vImper n pe ; ----e neg = vp.neg ! pol ; compl = neg.p2 ++ clpr.p2 ++ vp.comp ! agr ++ vp.ext ! pol in neg.p1 ++ verb ++ bindIf refl.p2 ++ refl.p1 ++ bindIf clpr.p3 ++ clpr.p1 ++ compl ; CopulaType = Bool ; selectCopula = \isEstar -> case isEstar of {True => estar_V ; False => copula} ; serCopula = False ; estarCopula = True ; negation : RPolarity => (Str * Str) = table { RPos => <[],[]> ; RNeg _ => <"no",[]> } ; conjThan = "que" ; conjThat = "que" ; subjIf = "si" ; clitInf b cli inf = inf ++ bindIf b ++ cli ; --- JS copied from DiffSpa relPron : Bool => AAgr => Case => Str = \\b,a,c => case c of { Nom | Acc => "que" ; CPrep P_a => "cuyo" ; _ => prepCase c ++ "cuyo" } ; pronSuch : AAgr => Str = aagrForms "tal" "tal" "tals" "tals" ; quelPron : AAgr => Str = aagrForms "qual" "qual" "quals" "quals" ; partQIndir = [] ; ---- ? reflPron : Number -> Person -> Case -> Str = \n,p,c -> let pro = argPron Fem n p c in case p of { P3 => case c of { Acc | CPrep P_a => "es" ; _ => "si" } ; _ => pro } ; argPron : Gender -> Number -> Person -> Case -> Str = let cases : (x,y : Str) -> Case -> Str = \me,moi,c -> case c of { Acc | CPrep P_a => me ; _ => moi } ; cases3 : (x,y,z : Str) -> Case -> Str = \les,leur,eux,c -> case c of { Acc => les ; CPrep P_a => leur ; _ => eux } ; in \g,n,p -> case of { <_,Sg,P1> => cases "em" "mí" ; <_,Sg,P2> => cases "et" "tú" ; <_,Pl,P1> => cases "ens" "nosaltres" ; --- nosotros <_,Pl,P2> => cases "us" "vosaltres" ; --- vosotros => cases3 "la" "li" "ella" ; => cases3 "el" "li" "ell" ; => cases3 "les" "les" "elles" ; => cases3 "els" "els" "ells" } ; vRefl _ = VRefl ; isVRefl : VType -> Bool = \ty -> case ty of { VRefl => True ; _ => False } ; auxPassive : Verb = verbBeschH (estar_54 "estar") ; copula = verbBeschH (ser_52 "ser") ; estar_V = verbBeschH (estar_54 "estar") ; haver_V : Verb = verbBeschH (haver_59 "haver" True) ; verbBeschH : Verbum -> Verb = \v -> verbBesch v ** {vtyp = VHabere ; p = []} ; subjPron = \_ -> [] ; polNegDirSubj = RPos ; }