--# -path=.:../romance:../abstract:../common:prelude instance DiffCat of DiffRomance = open CommonRomance, PhonoCat, BeschCat, Prelude in { flags optimize=noexpand ; 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 => "de" ; CPrep P_a => "a" } ; artDef : Gender -> Number -> Case -> Str = \g,n,c -> case of { => pre {"del" ; ["de l'"] / vocalForta} ; => pre {"al" ; ["a l'"] / vocalForta} ; => elisEl ; => prepCase c ++ elisLa ; <_, Pl, CPrep P_de> => "dels" ; <_, Pl, CPrep P_a> => "als" ; => "els" ; => "les" } ; artIndef = \g,n,c -> case of { => genForms ["d' un"] ["d' una"] ! g ; => genForms ["d' uns"] ["d' unes"] ! g ; => prepCase c ++ genForms "un" "una" ! g ; => prepCase c ++ genForms "uns" "unes" ! g } ; possCase = \_,_,c -> prepCase c ; partitive = \g,c -> case c of { CPrep P_de => "de" ; _ => prepCase c ++ artDef g Sg (CPrep P_de) } ; conjunctCase : NPForm -> NPForm = \c -> case c of { Ton Nom | Aton Nom => Ton Nom ; _ => Ton Acc } ; auxVerb : VType -> (VF => Str) = \_ -> haver_V.s ; partAgr : VType -> VPAgr = \vtyp -> vpAgrNone ; 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} ; 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 clpr.p3 ++ clpr.p1 ++ compl ; negation : Polarity => (Str * Str) = table { Pos => <[],[]> ; Neg => <"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 => "se" ; _ => "sÌ" } ; _ => 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 : VType = VRefl ; isVRefl : VType -> Bool = \ty -> case ty of { VRefl => True ; _ => False } ; auxPassive : Verb = copula ; copula = verbBeschH (ser_52 "ser") ; haver_V : Verb = verbBeschH (haver_59 "haver" True) ; verbBeschH : Verbum -> Verb = \v -> verbBesch v ** {vtyp = VHabere} ; }