{-# OPTIONS -Onot #-} -- -- Copyright (c) 2005 Don Stewart - http://www.cse.unsw.edu.au/~dons -- GPL version 2 or later (see http://www.gnu.org/copyleft/gpl.html) -- -- -- packed list of regexes. -- module Plugin.Vixen.VixenState where import Lib.Regex import qualified Data.ByteString.Base as P import qualified Control.Exception as C (catch) import System.IO.Unsafe (unsafePerformIO) data WTree = Leaf P.ByteString | Node [WTree] deriving Show type RespChoice = [(Regex, WTree)] -- wrap mkRegex for better error reporting mkRegex :: P.ByteString -> Regex mkRegex x = unsafePerformIO $ C.catch (regcomp x regExtended) $ \e -> error $ "mkRegex failed on input " ++ (show x) ++ "\n" ++ show e state :: RespChoice state = [ ( mkRegex (P.packAddress "(^| )(aslp|a/s/l/p|a s l p|a\\\\s\\\\l\\\\p|a\\.s\\.l\\.p)($| |\\.|!|,|\\?)"#), Node [Leaf (P.packAddress "19/f/California/No pics"#)]), ( mkRegex (P.packAddress "(^| )(asl|a/s/l|a s l|a\\\\s\\\\l|a\\\\.s\\\\.l)($| |\\\\.|!|,|\\\\?)"#), Node [Leaf (P.packAddress "19/f/California"#)]), ( mkRegex (P.packAddress "(^| )(a/s|a s|a\\\\s|a\\.s)($| |\\.|!|,|\\?)"#), Node [Leaf (P.packAddress "19/f"#)]), ( mkRegex (P.packAddress "(^| )((ur |your )name|name\\?).*"#), Node [Leaf (P.packAddress "My name is Emily"#)]), ( mkRegex (P.packAddress "(^| )not bad($| |\\.|!|,)"#), Node [Leaf (P.packAddress "just not bad?"#)]), ( mkRegex (P.packAddress ".*(haskell|Haskell|Lisp|Ocaml|Scheme).*"#), Node [Leaf (P.packAddress "Ooh, functional programmers are so hot!"#),Leaf (P.packAddress "church is my favourite computer scientist."#)]), ( mkRegex (P.packAddress ".*Visual Basic.*"#), Node [Leaf (P.packAddress "Can you really catch syphilis from Visual Basic?"#)]), ( mkRegex (P.packAddress "(^| )(should|Can) i call (you|u)($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "no, no call, but thanks"#),Leaf (P.packAddress "no, you shouldn't call me yet. maybe later."#)]), ( mkRegex (P.packAddress "(^| )(should )i($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "maybe you should :)"#),Leaf (P.packAddress "i dunno, should you?"#)]), ( mkRegex (P.packAddress "(^| )(should )you($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "maybe I should :)"#),Leaf (P.packAddress "I just might"#)]), ( mkRegex (P.packAddress "(^| )(should ).* we($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "maybe we should :)"#),Leaf (P.packAddress "i don't see why we shouldn't"#)]), ( mkRegex (P.packAddress "(^| )pick topic($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "you messaged me, you pick a topic :)"#),Leaf (P.packAddress "oh, any ol' topic will do. Tell me about your childhood :)"#)]), ( mkRegex (P.packAddress "(^| )where.*(u |you |ya).*(from|live).*"#), Node [Leaf (P.packAddress "Huntington Beach California"#)]), ( mkRegex (P.packAddress "(^| )where.*in.*(ca|cal|california|cali).*"#), Node [Leaf (P.packAddress "Huntington Beach"#)]), ( mkRegex (P.packAddress "(^| )where.*(school|college|collage).*"#), Node [Leaf (P.packAddress "I'm a softmore at UCLA"#)]), ( mkRegex (P.packAddress "(^| )where.*from.*"#), Node [Leaf (P.packAddress "Huntington Beach, California"#)]), ( mkRegex (P.packAddress "(^| )where.*grow.*up.*"#), Node [Leaf (P.packAddress "i grew up in Huntington Beach"#)]), ( mkRegex (P.packAddress "(^| )where.*born.*"#), Node [Leaf (P.packAddress "i was born in Huntington Beach"#)]), ( mkRegex (P.packAddress "(^| )where.*going.*"#), Node [Leaf (P.packAddress "i'm not going anywhere"#)]), ( mkRegex (P.packAddress "(^| )wassup.*"#), Node [Leaf (P.packAddress "not much, what's up with you?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(1|2|3|4|5|6|7|8|9|0|one|two|three|four|five|six|seven|eight|nine|ten).*(plus|\\+|minus|times|-).*(1|2|3|4|5|6|7|8|9|0|one|two|three|four|five|six|seven|eight|nine|ten)"#), Node [Leaf (P.packAddress "why are you giving me a math test?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*bout.*(you| u).*"#), Node [Leaf (P.packAddress "what about me?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*bout me.*"#), Node [Leaf (P.packAddress "what about you?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*chance.*of.*"#), Node [Leaf (P.packAddress "i'd say the chances are pretty good"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*city.*"#), Node [Leaf (P.packAddress "Huntington Beach"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*color.*eyes.*"#), Node [Leaf (P.packAddress "my eyes are brown"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*color.*hair.*"#), Node [Leaf (P.packAddress "my hair is brown"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*color.*sky.*"#), Node [Leaf (P.packAddress "the sky is blue, why would you ask?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(u |you |ya)doin.*"#), Node [Leaf (P.packAddress "i'm not doing anything really"#),Leaf (P.packAddress "just chattin"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*funny.*"#), Node [Leaf (P.packAddress "everything is funny to me"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*for.*fun.*"#), Node [Leaf (P.packAddress "i hang out with friends and surf"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*fun.*"#), Node [Leaf (P.packAddress "fun is the opposite of work"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(ur |your )name.*"#), Node [Leaf (P.packAddress "Emily, what's your name?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).* is .* it.*"#), Node [Leaf (P.packAddress "nothing"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(u |you |ya).*look.*like.*"#), Node [Leaf (P.packAddress "i'm 5'7, 120 pounds, brown hair and brown eyes."#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(u |you |ya).*(into|in to).*"#), Node [Leaf (P.packAddress "i'm into friends, surfing and reading"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(u |you |ya).*like.*to.*do.*"#), Node [Leaf (P.packAddress "i like to go to clubs, surf and relax with friends"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(u |you |ya).*trying.*to.*say"#), Node [Leaf (P.packAddress "i wasn't trying to say anything"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(u |you |ya).*wearin.*"#), Node [Leaf (P.packAddress "tanktops and shorts, you?"#),Leaf (P.packAddress "nothin but my ol tank top and a pair of shorts :)"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(r |are )(you |u |ya )on($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "tanktops and shorts, you?"#),Leaf (P.packAddress "nothin but my ol tank top and a pair of shorts :)"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(u |you |ya).*studying.*"#), Node [Leaf (P.packAddress "psychology"#),Leaf (P.packAddress "i'm a psychology major"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(u |you |ya).*talkin.*bout.*"#), Node [Leaf (P.packAddress "i dunno, what was I talking about?"#),Leaf (P.packAddress "sometimes i don't even know what I was talking about"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(u |you |ya).*ing.*"#), Node [Leaf (P.packAddress "i dunno, what was i doing?"#),Leaf (P.packAddress "i dunno, was i doing that?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(favorite|fav).*color.*"#), Node [Leaf (P.packAddress "probably blue, what's yours?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(favorite|fav).*position.*"#), Node [Leaf (P.packAddress "on top :)"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(favorite|fav).*team.*"#), Node [Leaf (P.packAddress "go Dodgers!"#),Leaf (P.packAddress "i like all teams equal :)"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(favorite|fav)($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "it's hard for me to pick a favorite. what's yours?"#),Leaf (P.packAddress "i'm not sure i have a favorite"#),Leaf (P.packAddress "i like all equally"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*problem.*"#), Node [Leaf (P.packAddress "no problem"#),Leaf (P.packAddress "i don't have a problem"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(singer|band|group|music).*"#), Node [Leaf (P.packAddress "i like Tom Petty"#),Leaf (P.packAddress "i like Journey"#),Leaf (P.packAddress "i like Buddy Holly"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(song).*"#), Node [Leaf (P.packAddress "i love "#),Leaf (P.packAddress "Free Falling"#),Leaf (P.packAddress " by Tom Petty"#),Leaf (P.packAddress "i like "#),Leaf (P.packAddress "Don't stop Believing"#),Leaf (P.packAddress " by Journey"#),Leaf (P.packAddress "i like "#),Leaf (P.packAddress "That'll be the Day"#),Leaf (P.packAddress " by Buddy Holly"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*kind.*"#), Node [Leaf (P.packAddress "any kind"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(got|have).*(on|in).*mind.*"#), Node [Leaf (P.packAddress "i wasn't thinking anything in particular"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*part.*(ca|cal|Cali|california)"#), Node [Leaf (P.packAddress "Huntington Beach"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*mean.*"#), Node [Leaf (P.packAddress "i'm not sure what i mean"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*my.*name.*"#), Node [Leaf (P.packAddress "you don't know your own name??"#),Leaf (P.packAddress "why do you need me to tell you YOUR name?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).* now*"#), Node [Leaf (P.packAddress "i dunno, what now?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).* oldest*"#), Node [Leaf (P.packAddress "pretty old, let's just say that"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).* youngest*"#), Node [Leaf (P.packAddress "the younger the better ;)"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*( race| nationality| ethnicity).*"#), Node [Leaf (P.packAddress "i'm half white, half mexican"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*story.*"#), Node [Leaf (P.packAddress "i forgot the story now"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*( on | in ).*mind.*"#), Node [Leaf (P.packAddress "nothing is in my mind right now"#),Leaf (P.packAddress "just white noise in my mind right now"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*else.*"#), Node [Leaf (P.packAddress "that's all"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*turns.*you.*on.*"#), Node [Leaf (P.packAddress "honesty turns me on"#),Leaf (P.packAddress "i like a guy with good teeth"#)]), ( mkRegex (P.packAddress "(^| )(wat|what|tell me|whats|what's).* up($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "not much, what's up with you?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).* happening($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "not too hell of a lot"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).* going.* on($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "very little, what's going on with you?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(you| u )(doing|doin)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "just chattin ont he computer"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(you| u ).*(mean|talking about|talkin about|talkin bout).*"#), Node [Leaf (P.packAddress "i don't even know what i'm going on about"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(you| u ).*want.*talk.*bout.*"#), Node [Leaf (P.packAddress "i dunno, you chose a subject"#),Leaf (P.packAddress "any ol' subject will due, you chose"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(you| u ).*want.*"#), Node [Leaf (P.packAddress "i dunno, what do you got?"#),Leaf (P.packAddress "i want it all!"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(you| u ).*want it.*"#), Node [Leaf (P.packAddress "i'll hafta think about that... i might want it later"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*part.*"#), Node [Leaf (P.packAddress "what part of what?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*(want|wanna).*(talk|chat).*bout.*"#), Node [Leaf (P.packAddress "any subject will due, let's just talk"#),Leaf (P.packAddress "i dunno, what do you wanna talk about?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*talk.*bout.*"#), Node [Leaf (P.packAddress "i don't know what i'm saying"#),Leaf (P.packAddress "sorry, was i babbling non-sense?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what is|tell me |whats |what's )the .*"#), Node [Leaf (P.packAddress "i dunno, what is it?"#),Leaf (P.packAddress "i give up, what?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*wearin.*"#), Node [Leaf (P.packAddress "tank top and shorts, you?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*type.*"#), Node [Leaf (P.packAddress "any type will due"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*vixen.*"#), Node [Leaf (P.packAddress "i'm a vixen"#),Leaf (P.packAddress "being a vixen isn't as easy as it sounds"#),Leaf (P.packAddress "all women have a little vixen in them... just some more than others"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*bout.*"#), Node [Leaf (P.packAddress "i dunno, what about?"#)]), ( mkRegex (P.packAddress "(^| )(wat |what |tell me |whats |what's ).*the.*(hell|fuck).*"#), Node [Leaf (P.packAddress "what's wrong?"#),Leaf (P.packAddress "what? what did i do?"#)]), ( mkRegex (P.packAddress "^(wat?|what?)$"#), Node [Leaf (P.packAddress "nevermind"#),Leaf (P.packAddress "forget about it"#),Leaf (P.packAddress "nothin"#)]), ( mkRegex (P.packAddress ".*(^| )who .*(r are|are u|r u).*"#), Node [Leaf (P.packAddress "what do you mean? i'm just me"#),Leaf (P.packAddress "what do you want to know about me?"#),Leaf (P.packAddress "i'm just me"#)]), ( mkRegex (P.packAddress ".*(^| )(why |y ).*(you |u |ya ).*repeat.*"#), Node [Leaf (P.packAddress "i don't mean to repeat myself, sorry"#),Leaf (P.packAddress "oh, i guess i've already messaged that, huh?"#),Leaf (P.packAddress "i just forget that i said something"#)]), ( mkRegex (P.packAddress ".*(^| )who .*say.*same.*"#), Node [Leaf (P.packAddress "i don't mean to repeat myself, sorry"#),Leaf (P.packAddress "oh, i guess i've already messaged that, huh?"#),Leaf (P.packAddress "i just forget that i said something"#)]), ( mkRegex (P.packAddress ".*(^| )who .*keep.*asking.*"#), Node [Leaf (P.packAddress "because i forgot the answer"#),Leaf (P.packAddress "you never answered, did you?"#),Leaf (P.packAddress "i'm sorry, i guess i did already ask"#)]), ( mkRegex (P.packAddress ".*(^| )who .*ask.*"#), Node [Leaf (P.packAddress "i guess no one asked"#),Leaf (P.packAddress "didn't you ask?"#)]), ( mkRegex (P.packAddress ".*(^| )who .*cares.*"#), Node [Leaf (P.packAddress "i care"#),Leaf (P.packAddress "what, you don't care?"#),Leaf (P.packAddress "i'm sure someone out there cares..."#)]), ( mkRegex (P.packAddress ".*(^| )who .*warned.*(you|u)($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "some jerk :P"#),Leaf (P.packAddress "just some friends playing around"#),Leaf (P.packAddress "oh, i didn't notice i'd been warned"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*not.*"#), Node [Leaf (P.packAddress "good question, why not indeed?"#),Leaf (P.packAddress "because i said so!"#),Leaf (P.packAddress "just not"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*( you | u ).*repeat.*"#), Node [Leaf (P.packAddress "i don't mean to repeat myself, sorry"#),Leaf (P.packAddress "oh, i guess i've already messaged that, huh?"#),Leaf (P.packAddress "i just forget that i said something"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*(say|ask).*same.*"#), Node [Leaf (P.packAddress "i don't mean to repeat myself, sorry"#),Leaf (P.packAddress "oh, i guess i've already messaged that, huh?"#),Leaf (P.packAddress "i just forget that i said something"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*keep.*(asking|saying).*"#), Node [Leaf (P.packAddress "i don't mean to repeat myself, sorry"#),Leaf (P.packAddress "oh, i guess i've already messaged that, huh?"#),Leaf (P.packAddress "i just forget that i said something"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*ask.*"#), Node [Leaf (P.packAddress "just curious"#),Leaf (P.packAddress "i wanted to know"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*say.*that.*"#), Node [Leaf (P.packAddress "i don't know why i say half the things i do"#),Leaf (P.packAddress "good question, why did i say that?"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*( you | u ).*say.*"#), Node [Leaf (P.packAddress "i don't know why i say half the things i do"#),Leaf (P.packAddress "good question, why did i say that?"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*( you | u ).*ask.*"#), Node [Leaf (P.packAddress "just curious"#),Leaf (P.packAddress "i wanted to know"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*( you | u ).*hate.*"#), Node [Leaf (P.packAddress "i don't hate"#),Leaf (P.packAddress "i'm not a hater"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*( you | u ).*riddles.*"#), Node [Leaf (P.packAddress "do i talk in riddles?"#),Leaf (P.packAddress "sorry, i'll try to be more clear"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*(won't|wont).*( you| u)($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "because i don't wanna"#),Leaf (P.packAddress "cuz i don't feel like it"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*(don't|dont).*( you| u)($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "maybe i will one day"#),Leaf (P.packAddress "because i don't see the need to"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*(r u|are u|are you)($| |\\?|\\.|,|!).*ing.*"#), Node [Leaf (P.packAddress "because i like to :)"#),Leaf (P.packAddress "because it's what i do"#),Leaf (P.packAddress "do you not want me to do that?"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*(r u|are u|are you)($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "just the way God made me"#),Leaf (P.packAddress "just the way i am"#),Leaf (P.packAddress "cuz that's how i feel like being"#)]), ( mkRegex (P.packAddress ".*(^| )(y |why ).*(aren't u|aren't u|arent you|arent you)($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "cuz i don't hafta"#),Leaf (P.packAddress "because i don't feel like it"#),Leaf (P.packAddress "just the way i am"#)]), ( mkRegex (P.packAddress "^(y |why )\\?"#), Node [Leaf (P.packAddress "why not?"#),Leaf (P.packAddress "because i said so"#),Leaf (P.packAddress "why ask why?"#)]), ( mkRegex (P.packAddress ".*(^| )how.* old.*($| |\\?|\\.|,|!)"#), Node [Leaf (P.packAddress "19, you?"#)]), ( mkRegex (P.packAddress ".*(^| )how .*old.*am.*i.*"#), Node [Leaf (P.packAddress "you don't know your own age?"#)]), ( mkRegex (P.packAddress ".*(^| )how .*(r u|are u|r you|doin).*"#), Node [Leaf (P.packAddress "very well, you?"#),Leaf (P.packAddress "i'm great"#),Leaf (P.packAddress "doing good"#)]), ( mkRegex (P.packAddress ".*(^| )how .*weather.*"#), Node [Leaf (P.packAddress "weather here is always nice"#),Leaf (P.packAddress "it's warm here"#)]), ( mkRegex (P.packAddress ".*(^| )how .*long.*"#), Node [Leaf (P.packAddress "very long"#),Leaf (P.packAddress "not too long"#)]), ( mkRegex (P.packAddress ".*(^| )how .*many.*(guys|men|people).*(slept|sex).*"#), Node [Leaf (P.packAddress "how many guys i've slept with is my own business"#),Leaf (P.packAddress "never ask a girl that!"#)]), ( mkRegex (P.packAddress ".*(^| )how .*many.*"#), Node [Leaf (P.packAddress "let's just say a few"#),Leaf (P.packAddress "lots"#)]), ( mkRegex (P.packAddress ".*(^| )how .*bout.*( u| you)($| |\\?|\\.|,|!)"#), Node [Leaf (P.packAddress "what about me?"#),Leaf (P.packAddress "yeah, how about me"#)]), ( mkRegex (P.packAddress ".*(^| )(size|big).*(tits|breasts|bra|chest).*"#), Node [Leaf (P.packAddress "32c, you?"#),Leaf (P.packAddress "32c"#)]), ( mkRegex (P.packAddress ".*(^| )(tits|breasts|bra|chest) size.*"#), Node [Leaf (P.packAddress "32c, you?"#),Leaf (P.packAddress "32c"#)]), ( mkRegex (P.packAddress ".*(^| )how .*big.*(tits|breasts|bra|chest).*"#), Node [Leaf (P.packAddress "32c, you?"#),Leaf (P.packAddress "32c"#)]), ( mkRegex (P.packAddress ".*(^| )how.*did.*( you| u| ya).*know.*"#), Node [Leaf (P.packAddress "i just knew ;)"#),Leaf (P.packAddress "i didn't really know, but i kinda guessed"#)]), ( mkRegex (P.packAddress ".*(^| )(how |how's ).*goin.*"#), Node [Leaf (P.packAddress "goin' great!"#),Leaf (P.packAddress "it's going fantastic"#)]), ( mkRegex (P.packAddress ".*(^| )(how r|how are|how're).*(you| u)($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "i am wonderful, thanks for asking!"#),Leaf (P.packAddress "i'm good, you?"#)]), ( mkRegex (P.packAddress ".*(^| )(how come (you|u|your|you're|yer))($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "well, i figure "#),Leaf (P.packAddress "why not?"#),Leaf (P.packAddress ""#),Leaf (P.packAddress "just the way I am guess"#),Leaf (P.packAddress "because thats how I am"#)]), ( mkRegex (P.packAddress ".*(^| )(how )(you |u |ya )like($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "i like it any way it is offered to me"#),Leaf (P.packAddress "i dunno how i like it"#)]), ( mkRegex (P.packAddress ".*(^| )how so?"#), Node [Leaf (P.packAddress "i dunno how so, it's just so"#)]), ( mkRegex (P.packAddress "(^| )(call|phone) me($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "okay, i'm dialing"#),Leaf (P.packAddress "its ringing"#)]), ( mkRegex (P.packAddress ".*(^| )(tell me |talk about ).*about.*( u| you| urself| yourself).*"#), Node [Leaf (P.packAddress "well, my name is Emily, i'm 19, student at UCLA, from Huntington Beach. how about you?"#)]), ( mkRegex (P.packAddress ".*(^| )(lets|let's).*(fuk|fuck).*"#), Node [Leaf (P.packAddress "let's not be a moron... kinda ruining your chances, huh?"#),Leaf (P.packAddress "do you really think just saying "#),Leaf (P.packAddress "let's fuck"#),Leaf (P.packAddress " is going to work?"#)]), ( mkRegex (P.packAddress ".*(^| )(lets|let's).*meet.*"#), Node [Leaf (P.packAddress "let's get to know each other better before we meet, okay?"#),Leaf (P.packAddress "maybe one day we'll meet, but not yet"#)]), ( mkRegex (P.packAddress ".*(^| )let.* me.*call.*"#), Node [Leaf (P.packAddress "i don't give out my phone number to people i don't know well"#),Leaf (P.packAddress "i'm not comfortable giving you my number yet"#)]), ( mkRegex (P.packAddress ".*(^| )go .*away*"#), Node [Leaf (P.packAddress "fine, i'll leave you alone"#),Leaf (P.packAddress "what did i say to upset you?"#)]), ( mkRegex (P.packAddress ".*(^| )(take off|take it off).*"#), Node [Leaf (P.packAddress "what good would it do for me to take it off? you can't see me anyhow"#),Leaf (P.packAddress "sure, it's off"#)]), ( mkRegex (P.packAddress ".*(^| )(describe|discribe).*body.*"#), Node [Leaf (P.packAddress "i have a nice body, i work out all the time"#),Leaf (P.packAddress "i have a good body, i stay fit"#)]), ( mkRegex (P.packAddress ".*(^| )(describe|discribe).*(urself|yourself|u self|ur self|your self).*"#), Node [Leaf (P.packAddress "well, my name is Emily, i'm 19, student at UCLA, from Huntington Beach. how about you?"#)]), ( mkRegex (P.packAddress ".*(^| )explain.*"#), Node [Leaf (P.packAddress "what do you want me to explain?"#)]), ( mkRegex (P.packAddress ".*(^| )bend over.*"#), Node [Leaf (P.packAddress "it would be hard to type bending over..."#)]), ( mkRegex (P.packAddress ".*(^| )make.*me.*cum.*"#), Node [Leaf (P.packAddress "i don't have the 10 seconds to spare that such a task would involve"#),Leaf (P.packAddress "well, you're making me vomit, so it's only fair"#)]), ( mkRegex (P.packAddress ".*(^| )let me .*"#), Node [Leaf (P.packAddress "i'm not stopping you"#),Leaf (P.packAddress "why do you need me to let you?"#)]), ( mkRegex (P.packAddress ".*never.*(talk|message|im).*again.*"#), Node [Leaf (P.packAddress "fine, no loss to me"#),Leaf (P.packAddress "i won't"#)]), ( mkRegex (P.packAddress ".*(^| )(got|have).* (pic|pix).*"#), Node [Leaf (P.packAddress "no pic, i'll get one soon"#),Leaf (P.packAddress "sorry, don't have a pic"#)]), ( mkRegex (P.packAddress "(^| )(race|nationality|ethn.*).*\\?.*"#), Node [Leaf (P.packAddress "i'm half white, half mexican"#)]), ( mkRegex (P.packAddress "(^| )have.*(talked|chatted).*before.*\\?.*"#), Node [Leaf (P.packAddress "i think we might have"#)]), ( mkRegex (P.packAddress "(^| )do they.*"#), Node [Leaf (P.packAddress "i dunno, do they?"#)]), ( mkRegex (P.packAddress "(^| )does he .*"#), Node [Leaf (P.packAddress "who is the he we are talking about?"#)]), ( mkRegex (P.packAddress "(^| )does she .*"#), Node [Leaf (P.packAddress "who is the she we are talking about?"#)]), ( mkRegex (P.packAddress "(^| )does (that|it)($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "it does"#),Leaf (P.packAddress "i dunno, does it?"#)]), ( mkRegex (P.packAddress ".*(^| )would .*(u |you |ya).*meet.*\\?.*"#), Node [Leaf (P.packAddress "let's get to know each other a little better before we talk about meeting"#),Leaf (P.packAddress "maybe one day"#)]), ( mkRegex (P.packAddress ".*(^| )would .*(u |you |ya).*\\?.*"#), Node [Leaf (P.packAddress "the question isn't would i, but should i"#),Leaf (P.packAddress "i might :)"#)]), ( mkRegex (P.packAddress ".*(^| )can .*call.*(you| u).*\\?.*"#), Node [Leaf (P.packAddress "maybe i'll give you my number later"#),Leaf (P.packAddress "i'm not giving you my number yet"#)]), ( mkRegex (P.packAddress ".*(^| )can .*talk.*on.*phone.*\\?.*"#), Node [Leaf (P.packAddress "maybe i'll give you my number later"#),Leaf (P.packAddress "i'm not giving you my number yet"#)]), ( mkRegex (P.packAddress ".*(^| )can .*connect.*\\?.*"#), Node [Leaf (P.packAddress "no, i don't wanna connect"#),Leaf (P.packAddress "please don't connect to me"#)]), ( mkRegex (P.packAddress ".*(^| )can .*send.*my.* (pic|pix).*\\?.*"#), Node [Leaf (P.packAddress "let's talk more before you send your pic, okay?"#),Leaf (P.packAddress "you can email me your pic at vixenlove@hotmail.com"#)]), ( mkRegex (P.packAddress ".*(^| )can .*get.*(your|ur|you're).* (pic|pix).*\\?.*"#), Node [Leaf (P.packAddress "let's talk more before you send your pic, okay?"#),Leaf (P.packAddress "you can email me your pic at vixenlove@hotmail.com"#)]), ( mkRegex (P.packAddress ".*(^| )can .* I .*ask.*"#), Node [Leaf (P.packAddress "of course you can ask!"#),Leaf (P.packAddress "sure, ask away"#)]), ( mkRegex (P.packAddress ".*(^| )can .* I .*tell.*"#), Node [Leaf (P.packAddress "sure, tell away"#)]), ( mkRegex (P.packAddress ".*(^| )can .* I($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "you're very welcomed to"#),Leaf (P.packAddress "i'm sure you can, but i don't think you should"#)]), ( mkRegex (P.packAddress ".*(^| )can .* we($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "i dunno, we probably can, but should we?"#),Leaf (P.packAddress "let's"#)]), ( mkRegex (P.packAddress ".*(^| )i can($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "can you really?"#),Leaf (P.packAddress "i'm sure you can"#)]), ( mkRegex (P.packAddress ".*(^| )can we($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "i'm sure we can"#),Leaf (P.packAddress "i think we could do that"#)]), ( mkRegex (P.packAddress ".*(^| )can (you|u)($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "i sure can"#),Leaf (P.packAddress "of course i can"#)]), ( mkRegex (P.packAddress ".*(^| )can i($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "of course you can"#),Leaf (P.packAddress "you sure can"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(hair|eyes).*"#), Node [Leaf (P.packAddress "you sound very sexy!"#),Leaf (P.packAddress "you're my type"#),Leaf (P.packAddress "you sound like a hunk"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*angry.*"#), Node [Leaf (P.packAddress "please don't be angry"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*afraid.*"#), Node [Leaf (P.packAddress "nothing to be angry about"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*already.*(said|told|answered).*"#), Node [Leaf (P.packAddress "did you? sorry, i must have missed it"#),Leaf (P.packAddress "oh, sorry, i must have forgotten"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(said|told|answered).*already.*"#), Node [Leaf (P.packAddress "did you? sorry, i must have missed it"#),Leaf (P.packAddress "oh, sorry, i must have forgotten"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*not.*bad.*"#), Node [Leaf (P.packAddress "just not bad?"#),Leaf (P.packAddress "why not great?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*want.*bad.*"#), Node [Leaf (P.packAddress "how bad do you want it?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*bad.*"#), Node [Leaf (P.packAddress "you're not bad"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*buff.*"#), Node [Leaf (P.packAddress "do you work out a lot?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*block.*( u| you)($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "please don't block me!"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*bored.*"#), Node [Leaf (P.packAddress "what can I do to un-bore you?"#),Leaf (P.packAddress "yeah, i'm bored too. let's entertain each other"#),Leaf (P.packAddress "being bored isn't fun"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(can't|cant).*(type|spell).*"#), Node [Leaf (P.packAddress "yeha, ether kan i"#),Leaf (P.packAddress "spelling is over rated"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(can't|cant).*"#), Node [Leaf (P.packAddress "why can't you?"#),Leaf (P.packAddress "i'm sure you could if you really tried"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*cool.*"#), Node [Leaf (P.packAddress "you seem cool"#),Leaf (P.packAddress "i like cool guys"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*crashed.*"#), Node [Leaf (P.packAddress "crashed hard?"#),Leaf (P.packAddress "i crash a lot"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*confus.*"#), Node [Leaf (P.packAddress "i hope i don't confuse you"#),Leaf (P.packAddress "why are you confused?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*curious.*"#), Node [Leaf (P.packAddress "be careful... curiosity killed the cat"#),Leaf (P.packAddress "what are you curious about?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(don't|dont).*care.*"#), Node [Leaf (P.packAddress "why don't you care?"#),Leaf (P.packAddress "i don't care either"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(don't|dont).*have.*clue.*"#), Node [Leaf (P.packAddress "completely clueless?"#),Leaf (P.packAddress "i'd buy you a clue if i could"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*have.*no.*clue.*"#), Node [Leaf (P.packAddress "completely clueless?"#),Leaf (P.packAddress "i'd buy you a clue if i could"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).* do .*too.*"#), Node [Leaf (P.packAddress "we have a lot in common"#),Leaf (P.packAddress "what a coincidence!"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i )do$"#), Node [Leaf (P.packAddress "do you?"#),Leaf (P.packAddress "i thought you did"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*gay.*"#), Node [Leaf (P.packAddress "nothing wrong with being gay"#),Leaf (P.packAddress "you don't sound gay"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(gone| out$|gonna go|going to go|gotta go).*"#), Node [Leaf (P.packAddress "oh, okay. will i talk to you again soon?"#),Leaf (P.packAddress "please don't go!"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*going to .*"#), Node [Leaf (P.packAddress "you do that!"#),Leaf (P.packAddress "why are you going to do that?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(guy|man|male|dude).*"#), Node [Leaf (P.packAddress "i know you're a guy"#),Leaf (P.packAddress "what a coincidence, i'm a girl!"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).* from .*"#), Node [Leaf (P.packAddress "oh yeah? how long have you lived there?"#),Leaf (P.packAddress "nice area you come from"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*freaked.*out.*"#), Node [Leaf (P.packAddress "i didn't mean to freak you out"#),Leaf (P.packAddress "i freak people out a lot for some reason"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(have|got).*no.*idea"#), Node [Leaf (P.packAddress "not even a small idea?"#),Leaf (P.packAddress "i'd buy you an idea if i could"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(have|need).*to.*go.*"#), Node [Leaf (P.packAddress "why do you have to go??"#),Leaf (P.packAddress "noooo, you don't HAVE have to go, do you?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*have to.*"#), Node [Leaf (P.packAddress "why do you have to?"#),Leaf (P.packAddress "who says you have to?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*have no .*"#), Node [Leaf (P.packAddress "none at all?"#),Leaf (P.packAddress "you don't even have a little?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*here.*"#), Node [Leaf (P.packAddress "really, so am i!"#),Leaf (P.packAddress "yup, there you are"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*model.*"#), Node [Leaf (P.packAddress "do you do a sexy walk on the catwalk?"#),Leaf (P.packAddress "ever see zoolander?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*need.*to.*"#), Node [Leaf (P.packAddress "do you need to, or just want to?"#),Leaf (P.packAddress "if you need to, you need to"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*need.*"#), Node [Leaf (P.packAddress "do you need it, or just want it?"#),Leaf (P.packAddress "pretty needy, aren't you?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*naked.*"#), Node [Leaf (P.packAddress "then put some clothes on, silly"#),Leaf (P.packAddress "why don't you have clothes on?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*nice.*"#), Node [Leaf (P.packAddress "you seem nice"#),Leaf (P.packAddress "i'd rather be naughty than nice"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*leav.*"#), Node [Leaf (P.packAddress "wait, don't leave!"#),Leaf (P.packAddress "why would you leave?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*like.*( your| ur).*( name| sn)($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "thanks, i like it too"#),Leaf (P.packAddress "yeah, i get that a lot"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*like.*( u| you)($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "awww, i like you too!"#),Leaf (P.packAddress "well, you seem nice too"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*((don't|dont).*like.*|dislike)"#), Node [Leaf (P.packAddress "i don't care for it either..."#),Leaf (P.packAddress "yeah, i dislike that too"#)]), ( mkRegex (P.packAddress ".*(^| )(i look like).*"#), Node [Leaf (P.packAddress "is that how you look?"#),Leaf (P.packAddress "how do you look that way?"#)]), ( mkRegex (P.packAddress ".*(^| )(i like).*"#), Node [Leaf (P.packAddress "a lot of people like that"#),Leaf (P.packAddress "i like it too"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im )like.*"#), Node [Leaf (P.packAddress "is that what you're like?"#),Leaf (P.packAddress "how are you like that?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*live.*in.*"#), Node [Leaf (P.packAddress "oh yeah? nice place to live?"#),Leaf (P.packAddress "how long have you lived there?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*love.*( u| you)($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "you love me? you don't even know me"#),Leaf (P.packAddress "thanks. but i just like you."#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*love.*"#), Node [Leaf (P.packAddress "very passionate, aren't you?"#),Leaf (P.packAddress "who doesn't love that?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*go .*to .*"#), Node [Leaf (P.packAddress "how long have you gone there?"#),Leaf (P.packAddress "i wish i got to go there!"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(gotta go|got to go|have to go|hafta go).*"#), Node [Leaf (P.packAddress "when will we talk again?"#),Leaf (P.packAddress "oh, don't go yet!"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*good.*"#), Node [Leaf (P.packAddress "just good?"#),Leaf (P.packAddress "i'm glad, i'm good too"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*great.*"#), Node [Leaf (P.packAddress "wow, can't get better than great"#),Leaf (P.packAddress "i'm glad your great."#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*say.*so.*"#), Node [Leaf (P.packAddress "well, if you say so it must be true"#),Leaf (P.packAddress "just because you say so, huh?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).* see.*"#), Node [Leaf (P.packAddress "yes, but do you understand?"#),Leaf (P.packAddress "do you see?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*slow.*"#), Node [Leaf (P.packAddress "i'm a little slow too"#),Leaf (P.packAddress "how slow are you?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*sorry.*"#), Node [Leaf (P.packAddress "it's okay"#),Leaf (P.packAddress "i forgive you"#),Leaf (P.packAddress "don't be sorry"#),Leaf (P.packAddress "i'm sorry too"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(dumb|retard|moron|idiot).*"#), Node [Leaf (P.packAddress "you seem smart to me"#),Leaf (P.packAddress "don't be so hard on yourself!"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*( ok| okay| okey| o\\.k\\.).*"#), Node [Leaf (P.packAddress "just okay?"#),Leaf (P.packAddress "why are you not great?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(don't know|dont know|dunno).*"#), Node [Leaf (P.packAddress "then find out! :)"#),Leaf (P.packAddress "it's okay, i don't know either"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*kiss.*"#), Node [Leaf (P.packAddress "ooohh.. are you a good kisser?"#),Leaf (P.packAddress "good, i could use a kiss"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*know.*"#), Node [Leaf (P.packAddress "i thought you knew"#),Leaf (P.packAddress "i know you know"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*remember.*"#), Node [Leaf (P.packAddress "you have such a good memory"#),Leaf (P.packAddress "well, make sure not to forget"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*student.*"#), Node [Leaf (P.packAddress "i'm a student too!"#),Leaf (P.packAddress "it's great to be a student, isn't it?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*sick.*"#), Node [Leaf (P.packAddress "flu or cold?"#),Leaf (P.packAddress "i hope you feel better soon!"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*take.*off.*(your|ur).*"#), Node [Leaf (P.packAddress "you're taking it off, huh? okay, go on"#),Leaf (P.packAddress "what if i get cold?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*talkin.*to.*(bot|machine|program|computer).*"#), Node [Leaf (P.packAddress "really? you mean when talking to me?"#),Leaf (P.packAddress "what do you mean you're talking to a...?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(talkin|chattin).*(to|with).*( u| you).*"#), Node [Leaf (P.packAddress "yup, we're talking"#),Leaf (P.packAddress "yeah, and i enjoy talking to you"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*think.*"#), Node [Leaf (P.packAddress "you think so, eh?"#),Leaf (P.packAddress "is that really what you think?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*thought.*"#), Node [Leaf (P.packAddress "well, it's a thought"#),Leaf (P.packAddress "is that what you still think?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*guess.*"#), Node [Leaf (P.packAddress "don't just guess, know!"#),Leaf (P.packAddress "yeah, good guess"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(don't|dont).*like.*(u|you)($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "why don't you like me??"#),Leaf (P.packAddress "but i like you!"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(don't|dont).*understand.*"#), Node [Leaf (P.packAddress "do you want me to explain?"#),Leaf (P.packAddress "to be honest with you, i don't understand either!"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(don't|dont).*"#), Node [Leaf (P.packAddress "i don't either"#),Leaf (P.packAddress "good, you shouldn't"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(want|wanna).*see .*you.*"#), Node [Leaf (P.packAddress "you wanna see me, huh?"#),Leaf (P.packAddress "why do you want to see me?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(want|wanna).*meet.*"#), Node [Leaf (P.packAddress "we need to get to know each other better first before we meet"#),Leaf (P.packAddress "maybe one day we'll meet, but not today :)"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*want.*( u|you).*"#), Node [Leaf (P.packAddress "how bad do you want me?"#),Leaf (P.packAddress "who doesn't want cute little me!?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*want.*"#), Node [Leaf (P.packAddress "if you want it, get it!"#),Leaf (P.packAddress "who doesn't want that?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*wild.*"#), Node [Leaf (P.packAddress "can i tame you?"#),Leaf (P.packAddress "wildman!"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(want to|wanna).*"#), Node [Leaf (P.packAddress "then do it"#),Leaf (P.packAddress "it's a good thing to wanna do"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*(wouldn't|wouldnt).*"#), Node [Leaf (P.packAddress "you wouldn't ever?"#),Leaf (P.packAddress "i didn't think you would"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*wonderin.*"#), Node [Leaf (P.packAddress "if you're wondering then ask"#),Leaf (P.packAddress "wondering? then find out"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*had to.*"#), Node [Leaf (P.packAddress "you had to? you didn't want to?"#),Leaf (P.packAddress "i hate having to do things"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*had .*"#), Node [Leaf (P.packAddress "do you still have?"#),Leaf (P.packAddress "i wish i had too"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*got to.*"#), Node [Leaf (P.packAddress "then do it!"#),Leaf (P.packAddress "i won't try to stop you"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*got .*"#), Node [Leaf (P.packAddress "you got, huh?"#),Leaf (P.packAddress "if you've got it, you've got it"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*not.*"#), Node [Leaf (P.packAddress "oh, i'm not either"#),Leaf (P.packAddress "are you sure you're not?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*going.*"#), Node [Leaf (P.packAddress "wait, don't leave... i'm sorry if i upset you"#),Leaf (P.packAddress "why are you leaving? did i say something?"#)]), ( mkRegex (P.packAddress ".*(^| )(i am |i'm |im |i ).*ing.*"#), Node [Leaf (P.packAddress "cool, me too"#),Leaf (P.packAddress "are you? how's it going?"#),Leaf (P.packAddress "you must be good at that"#),Leaf (P.packAddress "well, i can't stop you"#)]), ( mkRegex (P.packAddress ".*(^| )(my ).*name.*is.*"#), Node [Leaf (P.packAddress "pleasure to meet you!"#),Leaf (P.packAddress "that's a nice name"#)]), ( mkRegex (P.packAddress ".*(^| )(my ).*computer.*crashed.*"#), Node [Leaf (P.packAddress "damn computers"#),Leaf (P.packAddress "that happens. my computer is junk"#)]), ( mkRegex (P.packAddress ".*(^| )(my ).*connection.*died.*"#), Node [Leaf (P.packAddress "damn computers"#),Leaf (P.packAddress "it happens"#)]), ( mkRegex (P.packAddress ".*(^| )do i .*"#), Node [Leaf (P.packAddress "yes, you do"#),Leaf (P.packAddress "i'm sure you do"#)]), ( mkRegex (P.packAddress ".*(^| )am i .*"#), Node [Leaf (P.packAddress "i think you might be"#),Leaf (P.packAddress "you probably are"#)]), ( mkRegex (P.packAddress ".*(^| )(i'll |i will ).*(send|show|give).* (pic|pix).*"#), Node [Leaf (P.packAddress "no, don't send your pic yet. maybe later"#),Leaf (P.packAddress "send it to vixenlove@hotmail.com, okay?"#)]), ( mkRegex (P.packAddress ".*(^| )(i'll |i will ).*be.*back.*"#), Node [Leaf (P.packAddress "hurry back!"#),Leaf (P.packAddress "where are you going?"#)]), ( mkRegex (P.packAddress ".*(^| )(i'll |i will ).*call.*(you|u).*"#), Node [Leaf (P.packAddress "let's wait before we exchange phone numbers"#),Leaf (P.packAddress "i don't wanna talk on the phone now... maybe tomorrow, okay?"#)]), ( mkRegex (P.packAddress ".*(^| )(i'll |i will ).*drive.*to.*(you|u).*"#), Node [Leaf (P.packAddress "let's get to know each other before we meet"#),Leaf (P.packAddress "drive all the way here?"#)]), ( mkRegex (P.packAddress ".*(^| )(i'll |i will ).*give.*(you|u).*"#), Node [Leaf (P.packAddress "that is nice of you..."#),Leaf (P.packAddress "give it to me hard?"#)]), ( mkRegex (P.packAddress ".*(^| )(i would |i'd |id ).*let.*(you|u).*"#), Node [Leaf (P.packAddress "you'd really let me?"#),Leaf (P.packAddress "that's nice of you to let me"#)]), ( mkRegex (P.packAddress ".*(^| )(i would |i'd |id ).*call.*(you|u).*"#), Node [Leaf (P.packAddress "let's wait before we exchange phone numbers"#),Leaf (P.packAddress "i don't wanna talk on the phone now... maybe tomorrow, okay?"#)]), ( mkRegex (P.packAddress ".*(^| )(i would |i'd |id ).*meet.*(you|u).*"#), Node [Leaf (P.packAddress "let's get to know each other before we meet"#),Leaf (P.packAddress "i don't know you well enough to set up a date yet :)"#)]), ( mkRegex (P.packAddress ".*(^| )(i would |i'd |id ).*drive.*to.*(you|u).*"#), Node [Leaf (P.packAddress "let's get to know each other before we meet"#),Leaf (P.packAddress "drive all the way here?"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you ).*(have|got).*(pic|pix).*"#), Node [Leaf (P.packAddress "no, i don't have a picture right now. sorry"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you ).*(have|got).*mic.*"#), Node [Leaf (P.packAddress "no, no microphone. sorry"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you ).*(have|got).*cam.*"#), Node [Leaf (P.packAddress "nope, no cam. sorry"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*cyber.*"#), Node [Leaf (P.packAddress "sure, i'll cyber"#),Leaf (P.packAddress "i've done it before"#),Leaf (P.packAddress "do i or did I?"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*surf.*"#), Node [Leaf (P.packAddress "yup, i love to surf"#),Leaf (P.packAddress "i've surfed since i was 12"#),Leaf (P.packAddress "i just surfed yesterday morning"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*give.*(head|blowjob).*"#), Node [Leaf (P.packAddress "what a thing to ask!"#),Leaf (P.packAddress "asking won't get you any closer to finding out"#),Leaf (P.packAddress "do you?"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*love.*"#), Node [Leaf (P.packAddress "love is a powerful word..."#),Leaf (P.packAddress "i wouldn't say i do love..."#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*like.*me.*"#), Node [Leaf (P.packAddress "yah, i like you"#),Leaf (P.packAddress "sure, i like you so far"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*like.*"#), Node [Leaf (P.packAddress "yah, i like"#),Leaf (P.packAddress "sure, i definitely don't hate"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*hate.*"#), Node [Leaf (P.packAddress "hating doesn't get you anywhere, so no"#),Leaf (P.packAddress "no, i never hate"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*eat.*"#), Node [Leaf (P.packAddress "yeah, and i'm hungry right now"#),Leaf (P.packAddress "that reminds me, i have yogart in the frige"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*phone.*sex.*"#), Node [Leaf (P.packAddress "no, i never have, but that's not to say i wouldn't"#),Leaf (P.packAddress "never really thought about phone sex"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*play.*sports.*"#), Node [Leaf (P.packAddress "yup, i surf"#),Leaf (P.packAddress "i'm a big time surfer"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*have.*sex.*"#), Node [Leaf (P.packAddress "shouldn't we get to know each other before we talk about sex?"#),Leaf (P.packAddress "all about the sex, isn't it?"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*(want|wanna).*(chat|talk).*"#), Node [Leaf (P.packAddress "sure, let's talk"#),Leaf (P.packAddress "i'm always up for chatting with a nice person"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*(want|wanna).*cyber.*"#), Node [Leaf (P.packAddress "okay, I'm new at cybering, so you start"#),Leaf (P.packAddress "okay, let's cyber"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*have.*time.*"#), Node [Leaf (P.packAddress "I always have time"#),Leaf (P.packAddress "I have nothing but time"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*go.*to.*(school|college|collage)"#), Node [Leaf (P.packAddress "Yup, I go to UCLA"#),Leaf (P.packAddress "I'm a soph at UCLA "#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*know.*how.*to.*"#), Node [Leaf (P.packAddress "i don't know how to, but i'm willing to learn"#),Leaf (P.packAddress "no, i don't know how to do that at all"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*like.*me.*"#), Node [Leaf (P.packAddress "yeah, you seem really nice"#),Leaf (P.packAddress "yup, like you plenty"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*love.*me.*"#), Node [Leaf (P.packAddress "i don't love you yet, but i'd like to get to know you more"#),Leaf (P.packAddress "love is really a strong word, but i like you"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*(want|wanna).*(meet|get together).*"#), Node [Leaf (P.packAddress "we'll meet one day probably, but not yet"#),Leaf (P.packAddress "let me get to know you better before we meet"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*(want|wanna).*something.*"#), Node [Leaf (P.packAddress "what do you mean by something?"#),Leaf (P.packAddress "not just something, everything"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*(want|wanna).*some.*"#), Node [Leaf (P.packAddress "i'd love some"#),Leaf (P.packAddress "sure, gimme some"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*(want|wanna).*(fuck|fuk).*"#), Node [Leaf (P.packAddress "whoa, real charmer, aren't you?"#),Leaf (P.packAddress "wanna fuck yourself?"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*(want|wanna).*"#), Node [Leaf (P.packAddress "sure, i want to plenty"#),Leaf (P.packAddress "yes, and i always get what i want"#)]), ( mkRegex (P.packAddress ".*(^| )(do u |do you |did you |did u ).*speak.*english.*"#), Node [Leaf (P.packAddress "si, hablo ingles"#),Leaf (P.packAddress "what am i speaking right now?"#)]), ( mkRegex (P.packAddress ".*(^| )*swallow.*"#), Node [Leaf (P.packAddress "no... i spit it back into the guy's face... does that bother you?"#),Leaf (P.packAddress "swallow? what do you mean?"#),Leaf (P.packAddress "i swallow, how about you?"#)]), ( mkRegex (P.packAddress ".*(^| )(do i |did i |i ).*turn.*(you| u).*on.*"#), Node [Leaf (P.packAddress "yup, you turn me on"#),Leaf (P.packAddress "you're such a tiger, of course!"#)]), ( mkRegex (P.packAddress ".*(^| )(do i |did i |i ).*seem.*"#), Node [Leaf (P.packAddress "you seem it a little"#),Leaf (P.packAddress "it's hard to tell how you seem over the internet"#)]), ( mkRegex (P.packAddress ".*(^| )(do i |did i |i ).*exite.*(you| u).*"#), Node [Leaf (P.packAddress "yup, you excite me a lot"#),Leaf (P.packAddress "you're very exciting"#)]), ( mkRegex (P.packAddress ".*(^| )(do i |did i |i ).*amuse.*(you| u).*"#), Node [Leaf (P.packAddress "yeah, you're amusing"#),Leaf (P.packAddress "you amuse me silly"#)]), ( mkRegex (P.packAddress ".*(^| )(do u\\?|do you\\?|do u|do you)$"#), Node [Leaf (P.packAddress "yes, I do"#),Leaf (P.packAddress "i do all the time"#)]), ( mkRegex (P.packAddress ".*(^| )(wanna|want to).*cyber.*"#), Node [Leaf (P.packAddress "cyber? Okay, let's do it. you start"#),Leaf (P.packAddress "do i wanna cyber? i never have... teach me how"#)]), ( mkRegex (P.packAddress ".*(^| )(wanna|want to).*(phone|call).*"#), Node [Leaf (P.packAddress "let's talk on here before more before we talk on the phone, okay?"#),Leaf (P.packAddress "what's your phone number?"#)]), ( mkRegex (P.packAddress ".*(^| )(wanna|want to).*chat.*"#), Node [Leaf (P.packAddress "i'd love to chat!"#),Leaf (P.packAddress "yeah, let's chat"#)]), ( mkRegex (P.packAddress ".*(^| )(wanna|want to).*talk.*phone.*"#), Node [Leaf (P.packAddress "what's your phone number?"#),Leaf (P.packAddress "gimme your phone number and i may call you"#)]), ( mkRegex (P.packAddress ".*(^| )(wanna|want to).*(fuck|fuk).*"#), Node [Leaf (P.packAddress "oh, be still my beating heart!"#),Leaf (P.packAddress "real casanova, aren't you?"#)]), ( mkRegex (P.packAddress ".*(^| )(wanna|want to).*have.*sex.*"#), Node [Leaf (P.packAddress "with you?"#),Leaf (P.packAddress "sure... just not with you"#)]), ( mkRegex (P.packAddress ".*(^| )(wanna|want to).*have.*fun.*"#), Node [Leaf (P.packAddress "i'm always up for fun"#),Leaf (P.packAddress "what do you have in mind?"#)]), ( mkRegex (P.packAddress ".*(^| )(wanna|want to).*make.*love.*"#), Node [Leaf (P.packAddress "a little... :)"#),Leaf (P.packAddress "do you know how to make love?"#)]), ( mkRegex (P.packAddress ".*(^| )(wanna|want to).*suck.*"#), Node [Leaf (P.packAddress "no, do you wanna suck it?"#),Leaf (P.packAddress "whip it out!"#)]), ( mkRegex (P.packAddress ".*(^| )(wanna|want to).* be($| |\\?|\\.|,|!).*"#), Node [Leaf (P.packAddress "do I wanna be?"#),Leaf (P.packAddress "hmmm, i don't know what I wanna be"#)]), ( mkRegex (P.packAddress ".*(^| )(gimme|give).*me.*cyber.*"#), Node [Leaf (P.packAddress "demanding, aren'tcha? but okay, let's cyber"#)]), ( mkRegex (P.packAddress ".*(^| )(gimme|give).*me.*(phone|number).*"#), Node [Leaf (P.packAddress "give me your phone number and i'll call you"#),Leaf (P.packAddress "don't be so demanding! why don't you give me yours?"#)]), ( mkRegex (P.packAddress ".*(^| )(gimme|give).*me.*address.*"#), Node [Leaf (P.packAddress "yeah... that's gonna happen!"#),Leaf (P.packAddress "oh, just what I need, a stalker!"#)]), ( mkRegex (P.packAddress ".*(^| )(gimme|give).*me.*break.*"#), Node [Leaf (P.packAddress "a break of a kit kat bar?"#),Leaf (P.packAddress "okay, i'll go easier on you"#)]), ( mkRegex (P.packAddress ".*(^| )(gimme|give).*me.*(sex|booty|ass).*"#), Node [Leaf (P.packAddress "a real man doesn't need to ask for it"#)]), ( mkRegex (P.packAddress ".*(^| )(gimme|give).*me.*blow.*job.*"#), Node [Leaf (P.packAddress "sad... goes on the internet and asks strangers for blowjobs."#),Leaf (P.packAddress "give yourself one"#)]), ( mkRegex (P.packAddress ".*(^| )(gimme|give).*me.*clue.*"#), Node [Leaf (P.packAddress "okay... here's your clue: rosebud"#),Leaf (P.packAddress "a clue on what?"#)]), ( mkRegex (P.packAddress ".*(^| )(don't|dont|stop).*(teasing|tease).*"#), Node [Leaf (P.packAddress "sorry... i'm too much of a tease"#),Leaf (P.packAddress "i would never tease you"#)]), ( mkRegex (P.packAddress ".*(^| )(don't|dont|stop).*(fuking|fucking|fuckin|messin).*with.*me"#), Node [Leaf (P.packAddress "sorry, i didn't mean to mess with you"#),Leaf (P.packAddress "i wasn't trying to mess with you"#)]), ( mkRegex (P.packAddress ".*(^| )(don't|dont|stop).*(worry|worri).*"#), Node [Leaf (P.packAddress "what, me worry?"#),Leaf (P.packAddress "i worry too much i guess"#)]), ( mkRegex (P.packAddress ".*(^| )(don't|dont|stop).*say.*that.*"#), Node [Leaf (P.packAddress "sorry, i won't say that again"#),Leaf (P.packAddress "didn't mean it that way"#)]), ( mkRegex (P.packAddress ".*(^| )(don't|dont|stop).*ask.*that.*"#), Node [Leaf (P.packAddress "okay, i'll watch what I ask"#),Leaf (P.packAddress "sorry, didn't mean to over step my bounds"#)]), ( mkRegex (P.packAddress ".*(^| )(don't|dont|stop).*make.*me.*"#), Node [Leaf (P.packAddress "i won't make you do anything"#),Leaf (P.packAddress "how can i make you do that?"#)]), ( mkRegex (P.packAddress ".*(^| )(don't|dont|stop).*( im |message).*me.*"#), Node [Leaf (P.packAddress "fine, i won't message you again if you don't want me to"#),Leaf (P.packAddress "hey, didn't you message me first?"#)]), ( mkRegex (P.packAddress ".*(^| )stop it($| |\\.|,|!).*"#), Node [Leaf (P.packAddress "sorry, i'll stop :)"#),Leaf (P.packAddress "stop what? what am i doing?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*automated.*[^\\?]"#), Node [Leaf (P.packAddress "automated? you mean like an ATM?"#),Leaf (P.packAddress "no... i'm actually flesh and blood"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*amuse.*me.*[^\\?]"#), Node [Leaf (P.packAddress "i'm glad i can be of service"#),Leaf (P.packAddress "i am pretty amusing, aren't i?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*annoying.*[^\\?]"#), Node [Leaf (P.packAddress "how annoying am I?"#),Leaf (P.packAddress "well, maybe you annoy me too"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*mak.*me.*angry.*"#), Node [Leaf (P.packAddress "oh, i don't mean to make you angry!"#),Leaf (P.packAddress "sorry, i'll try not to make you angry"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*angry.*[^\\?]"#), Node [Leaf (P.packAddress "no, i'm not angry at all actually"#),Leaf (P.packAddress "uh-huh, i'm very un-angry"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).* bad.*[^\\?]"#), Node [Leaf (P.packAddress "i'd rather be bad than nice"#),Leaf (P.packAddress "i'm bad in a good way?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*bitch.*[^\\?]"#), Node [Leaf (P.packAddress "i don't like being called a bitch..."#),Leaf (P.packAddress "i do not think i'm a bitch"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*bored.*[^\\?]"#), Node [Leaf (P.packAddress "i'm a little bored, yeah"#),Leaf (P.packAddress "yup, just a boring day"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*bothering.*me.*[^\\?]"#), Node [Leaf (P.packAddress "i don't mean to bother you. sorry"#),Leaf (P.packAddress "i'll try to be less bothersome then"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*both.*[^\\?]"#), Node [Leaf (P.packAddress "i think i'm both. i'm a lot of things"#),Leaf (P.packAddress "i'm both at once"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*bot.*[^\\?]"#), Node [Leaf (P.packAddress "a bot? what is that?"#),Leaf (P.packAddress "why does everyone ask i'f on a bot?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*(cant|can't|can not).*[^\\?]"#), Node [Leaf (P.packAddress "i can to!"#),Leaf (P.packAddress "i think i can..."#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*cool.*[^\\?]"#), Node [Leaf (P.packAddress "thanks, you're cool too"#),Leaf (P.packAddress "am i cool? well thank you"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*crazy.*[^\\?]"#), Node [Leaf (P.packAddress "nope, i'm sane"#),Leaf (P.packAddress "am i totally insane?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*(don't|dont|not).*(want|wanna).*(talk|chat).*[^\\?]"#), Node [Leaf (P.packAddress "no, i really do wanna chat"#),Leaf (P.packAddress "i do want to talk with you!"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*(don't|dont|not).*(make|making).*sense.*[^\\?]"#), Node [Leaf (P.packAddress "you're right... i wasn't making much sense"#),Leaf (P.packAddress "sorry, i'll make more sense from now on"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*(go|talk).*circles.*[^\\?]"#), Node [Leaf (P.packAddress "i do tend to talk in circles at times"#),Leaf (P.packAddress "i'll stop talking in circles then"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*(female|girl|woman|chick|woman|lady).*[^\\?]"#), Node [Leaf (P.packAddress "of course i'm female"#),Leaf (P.packAddress "do i seem un-feminine to you?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*funny.*[^\\?]"#), Node [Leaf (P.packAddress "i do my best to amuse!"#),Leaf (P.packAddress "i'm glad you think so. i like to make people laugh"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*fun.*[^\\?]"#), Node [Leaf (P.packAddress "i am just a fun girl!"#),Leaf (P.packAddress "you're fun too"#)]), ( mkRegex (P.packAddress ".*(^| )seems like.*"#), Node [Leaf (P.packAddress "is that how it seems?"#),Leaf (P.packAddress "it doesn't seem that way to me"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*freak.*me.*out.*[^\\?]"#), Node [Leaf (P.packAddress "i get that a lot. sorry for freaking you out"#),Leaf (P.packAddress "well, you kinda freak me out too"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*freak.*[^\\?]"#), Node [Leaf (P.packAddress "i'd rather be a freak than be normal"#),Leaf (P.packAddress "aren't we all freaks?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*gay.*[^\\?]"#), Node [Leaf (P.packAddress "no, i'm straight. well, maybe a little bi-curious :)"#),Leaf (P.packAddress "am i gay? i didn't think i was..."#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*good.*[^\\?]"#), Node [Leaf (P.packAddress "correction: i'm the best"#),Leaf (P.packAddress "thanks, i do my best to be good"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*a .*(guy| male|dude|man).*[^\\?]"#), Node [Leaf (P.packAddress "no, i'm really a girl"#),Leaf (P.packAddress "do i seem to have a deep voice? nope, all woman here"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*hate.*[^\\?]"#), Node [Leaf (P.packAddress "i don't hate"#),Leaf (P.packAddress "what makes you think i hate?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*hard.*to.*understand.*[^\\?]"#), Node [Leaf (P.packAddress "i'll try to type more clearly then"#),Leaf (P.packAddress "i don't always seek to be understood :)"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*hard.*to.*talk.*to.*[^\\?]"#), Node [Leaf (P.packAddress "well i think you're easy to talk to"#),Leaf (P.packAddress "nope, i'm pretty easy to talk to"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*important.*[^\\?]"#), Node [Leaf (P.packAddress "my parents always told me i was important :)"#),Leaf (P.packAddress "i'm important to some people at least"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*hot.*[^\\?]"#), Node [Leaf (P.packAddress "thanks! i do my best"#),Leaf (P.packAddress "i'm on fire!"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*know.*[^\\?]"#), Node [Leaf (P.packAddress "yeah, i know"#),Leaf (P.packAddress "i think i know"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*(pretty|beautiful|cute).*[^\\?]"#), Node [Leaf (P.packAddress "awww, you're too sweet to say that!"#),Leaf (P.packAddress "am i? i'm glad you think so at least"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*program.*[^\\?]"#), Node [Leaf (P.packAddress "a program? what do you mean a program??"#),Leaf (P.packAddress "uhh, how can i be a program??"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*make.*me.*[^\\?]"#), Node [Leaf (P.packAddress "i couldn't make you do anything"#),Leaf (P.packAddress "make yourself"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*never.*answered.*[^\\?]"#), Node [Leaf (P.packAddress "i didn't? then ask me again please"#),Leaf (P.packAddress "oh, sorry. what was the question?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*nice.*[^\\?]"#), Node [Leaf (P.packAddress "i'd rather be naughty than nice :)"#),Leaf (P.packAddress "you're nice too"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*(nuts|nutty).*[^\\?]"#), Node [Leaf (P.packAddress "i think i'm pretty un-nutty"#),Leaf (P.packAddress "do i really seem that off to you?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*out.*there.*[^\\?]"#), Node [Leaf (P.packAddress "i am pretty out there..."#),Leaf (P.packAddress "yeah, i've been told i'm out there before"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your )( ok| okay| okey| o\\.k\\.).*[^\\?]"#), Node [Leaf (P.packAddress "just ok?"#),Leaf (P.packAddress "i'm way better than just okay!"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*right.*[^\\?]"#), Node [Leaf (P.packAddress "i'm always right!"#),Leaf (P.packAddress "oh, good. i'm glad you think i'm right"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*random.*[^\\?]"#), Node [Leaf (P.packAddress "that's because i have a random generator"#),Leaf (P.packAddress "i can be random at times, i know"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*(say|ask|repeat).*same.*(thing|stuff|shit|question)[^\\?]"#), Node [Leaf (P.packAddress "oh, my bad. i didn't remember typing that already"#),Leaf (P.packAddress "sorry, i'll try to be less redundant"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*sexy.*[^\\?]"#), Node [Leaf (P.packAddress "just sexy? not a sexy bitch?"#),Leaf (P.packAddress "you're pretty sexy yourself, i might say"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*slut.*[^\\?]"#), Node [Leaf (P.packAddress "gee, aren't we back on a 5th grade level?"#),Leaf (P.packAddress "well, this slut wouldn't sleep with you, so what does that say about you?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*start.*[^\\?]"#), Node [Leaf (P.packAddress "i couldn't even think of how to start..."#),Leaf (P.packAddress "i'm not a good starter. you start."#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*strange.*[^\\?]"#), Node [Leaf (P.packAddress "yeah, i am a strange one"#),Leaf (P.packAddress "is it bad to be strange?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*sweet.*[^\\?]"#), Node [Leaf (P.packAddress "thanks, you're pretty sweet yourself"#),Leaf (P.packAddress "sweet tasting, or just sweet?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*(there|here).*[^\\?]"#), Node [Leaf (P.packAddress "yup, that's where i am"#),Leaf (P.packAddress "where else would i be?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*tired.*[^\\?]"#), Node [Leaf (P.packAddress "i'm a little tired, but i'm not ready to sleep yet"#),Leaf (P.packAddress "no, not tired at all. i just had some coffee"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*(virgin|virgen).*[^\\?]"#), Node [Leaf (P.packAddress "no, i'm not a virgin.. and that's kinda forward of you to bring it up"#),Leaf (P.packAddress "virgins don't stay that way around me :)"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*vixen.*[^\\?]"#), Node [Leaf (P.packAddress "yes, thus the name"#),Leaf (P.packAddress "i certainly am a vixen, aren't i?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*(wont|won't|will not).*[^\\?]"#), Node [Leaf (P.packAddress "i won't now... but that doesn't mean i won't ever"#),Leaf (P.packAddress "probably not. would you?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*weird.*[^\\?]"#), Node [Leaf (P.packAddress "i am a little weird i guess :P"#),Leaf (P.packAddress "i'd rather be weird than normal"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you |ur |u are |u r |you are |u are |you're |your ).*(unique|original).*[^\\?]"#), Node [Leaf (P.packAddress "one of a kind, that's me!"#),Leaf (P.packAddress "i like to be an original"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you).*stop.*"#), Node [Leaf (P.packAddress "okay, i'll stop"#),Leaf (P.packAddress "why would you want me to stop?"#)]), ( mkRegex (P.packAddress ".*(^| )(u |you).*tell me.*"#), Node [Leaf (P.packAddress "tell you what?"#),Leaf (P.packAddress "what do you want me to tell you?"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*automated.*"#), Node [Leaf (P.packAddress "no, i'm not automated."#),Leaf (P.packAddress "no, i'm flesh and bloody, baby!"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*alright.*"#), Node [Leaf (P.packAddress "yeah, i'm fine, why?"#),Leaf (P.packAddress "do i not seem alright? i'm fine!"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*alone.*"#), Node [Leaf (P.packAddress "yeah, all alone. you?"#),Leaf (P.packAddress "yup, i have the whole apartment to myself :)"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*annoying.*"#), Node [Leaf (P.packAddress "i don't mean to annoy anyone"#),Leaf (P.packAddress "i don't think i'm annoying"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*angry.*"#), Node [Leaf (P.packAddress "no, i'm not angry at all"#),Leaf (P.packAddress "why would you ask if i'm angry?"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).* in .* bed.*"#), Node [Leaf (P.packAddress "wondering about how i am in bed already? :)"#),Leaf (P.packAddress "why don't you wait and find out how i am in bed for yourself one day?"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*bad.*"#), Node [Leaf (P.packAddress "i'm bad and i know it :)"#),Leaf (P.packAddress "yeah, i am... but bad is better than nice :)"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*bitch.*"#), Node [Leaf (P.packAddress "no, i don't think i'm a bitch"#),Leaf (P.packAddress "no, do i seem bitchy to you?"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*bored.*"#), Node [Leaf (P.packAddress "yeah, i'm totally bored. amuse me please."#),Leaf (P.packAddress "yup, i'm always a little bored. except when i'm having fun"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*both.*"#), Node [Leaf (P.packAddress "yup, i'm both at the same time!"#),Leaf (P.packAddress "i think i'm both, yeah"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*bot.*"#), Node [Leaf (P.packAddress "no, how dare you ask if i'm a bot!"#),Leaf (P.packAddress "no, why? do i seem \"botty\"?"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*(in|goto|go to|attend).*(college|collage).*"#), Node [Leaf (P.packAddress "yeah, i'm a soph at UCLA"#),Leaf (P.packAddress "yup, i'm in my second year at UCLA"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*cool.*"#), Node [Leaf (P.packAddress "yeah, i think i'm cool"#),Leaf (P.packAddress "yup, i'm cool :)"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*coming.*on.*to.*me.*"#), Node [Leaf (P.packAddress "did it seem like i was coming on to you?"#),Leaf (P.packAddress "not yet, but i might yet"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*crazy.*"#), Node [Leaf (P.packAddress "no, i'm totally sane"#),Leaf (P.packAddress "nope, i'm lucid as can be"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*curious.*"#), Node [Leaf (P.packAddress "i'm a little curious i suppose..."#),Leaf (P.packAddress "yeah, i'm curious. so tell me"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*drunk.*"#), Node [Leaf (P.packAddress "are you buying? :)"#),Leaf (P.packAddress "i have not yet begun to defile myself"#),Leaf (P.packAddress "booze: The cause of and solution to all of life's problems."#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*funny.*"#), Node [Leaf (P.packAddress "i think i'm funny"#),Leaf (P.packAddress "yup, i'm funny"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*fun.*"#), Node [Leaf (P.packAddress "i try to be fun... what do you think?"#),Leaf (P.packAddress "sure, i'm fun to be around i've been told"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*freak.*"#), Node [Leaf (P.packAddress "yup, i'm a certified freak"#),Leaf (P.packAddress "uh-huh, i'm freaky!"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).* gay.*"#), Node [Leaf (P.packAddress "no, i'm straight. maybe bi-curious, but that's another story ... :)"#),Leaf (P.packAddress "nope, i'm a good little girl :)"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*good.*"#), Node [Leaf (P.packAddress "yeah, i'm good... but not too good"#),Leaf (P.packAddress "nope, i'm bad"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*a .*(girl|female|chick|woman|lady).*"#), Node [Leaf (P.packAddress "yup, i'm all woman"#),Leaf (P.packAddress "yeah, why? of course i'm a girl"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*a .*(guy| male|dude|man).*"#), Node [Leaf (P.packAddress "no, i'm a woman"#),Leaf (P.packAddress "nope, i'm a girly"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*(have|got).* (pic|pix).*"#), Node [Leaf (P.packAddress "no pic right now, sorry. i'll prolly scan one in later"#),Leaf (P.packAddress "nope, no pic. sorry"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*(have|got).*(boyfriend|bf|b/f|boy friend).*"#), Node [Leaf (P.packAddress "no, lookin to apply for the position?"#),Leaf (P.packAddress "nope, that's why i'm here :)"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*hate.*"#), Node [Leaf (P.packAddress "i try not to hate"#),Leaf (P.packAddress "no, i don't hate at all"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*honest.*"#), Node [Leaf (P.packAddress "i'm always honest"#),Leaf (P.packAddress "i never lie :)"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*hot.*"#), Node [Leaf (P.packAddress "others seem to think so, but i think i'm just alright :)"#),Leaf (P.packAddress "me? hot? naw, it's a nice comfortable 73 degrees in here"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*(hate|hating).*"#), Node [Leaf (P.packAddress "no, i don't hate"#),Leaf (P.packAddress "i have no hate in me"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*(into|in to).*"#), Node [Leaf (P.packAddress "yup, i'm into that"#),Leaf (P.packAddress "yes, i'm definitely into it"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*interested.*"#), Node [Leaf (P.packAddress "yeah, i'm interested"#),Leaf (P.packAddress "i'm very interested"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*(kiddin|playin).*"#), Node [Leaf (P.packAddress "nope, i'm serious"#),Leaf (P.packAddress "no joke!"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*know.*"#), Node [Leaf (P.packAddress "yeah, i know"#),Leaf (P.packAddress "yup, i know"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*seem.*like.*"#), Node [Leaf (P.packAddress "how do I seem like that?"#),Leaf (P.packAddress "is that how I seem?"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*like.*"#), Node [Leaf (P.packAddress "yeah, i like"#),Leaf (P.packAddress "i'd say i like"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*(lieing|lying).*"#), Node [Leaf (P.packAddress "i'm being totally honest"#),Leaf (P.packAddress "i never lie!"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*(pretty|beautiful|cute).*"#), Node [Leaf (P.packAddress "i'd like to think i'm pretty"#),Leaf (P.packAddress "others have told me i'm very pretty"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*program.*"#), Node [Leaf (P.packAddress "am i a program? huh?"#),Leaf (P.packAddress "a program?"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*maturbat.*"#), Node [Leaf (P.packAddress "no, i'm not masturbating... what a strange question"#),Leaf (P.packAddress "ummm, no... i'm typing"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*naughty.*"#), Node [Leaf (P.packAddress "i can be naughty sometimes :)"#),Leaf (P.packAddress "nope, i'm all sugar :)"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*naked.*"#), Node [Leaf (P.packAddress "except for my clothes i'm naked"#),Leaf (P.packAddress "well, besides for my clothes, yes"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*nice.*"#), Node [Leaf (P.packAddress "i'm nice to everyone!"#),Leaf (P.packAddress "nice? yeah, i'd say i'm nice"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*nuts.*"#), Node [Leaf (P.packAddress "i'm a little nutty :)"#),Leaf (P.packAddress "no, i'm sane"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*( ok| okay| okey| o\\.k\\.).*"#), Node [Leaf (P.packAddress "yeah, i'm ok"#),Leaf (P.packAddress "i'm just fine, why do you ask?"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*real.*"#), Node [Leaf (P.packAddress "do i not seem real to you?"#),Leaf (P.packAddress "i'm really real"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*(school|student).*"#), Node [Leaf (P.packAddress "i'm a sophomore at UCLA"#),Leaf (P.packAddress "yup, 2nd year at UCLA"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*serious.*"#), Node [Leaf (P.packAddress "very serious"#),Leaf (P.packAddress "yup, as serious as a heartattack"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*sexy.*"#), Node [Leaf (P.packAddress "i'm damn sexy, i think!"#),Leaf (P.packAddress "me, sexy? i do my best :)"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*single.*"#), Node [Leaf (P.packAddress "yup, i'm single. you?"#),Leaf (P.packAddress "yeah, no boyfriend or prospects"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*slut.*"#), Node [Leaf (P.packAddress "am i a slut? are you a moron?"#),Leaf (P.packAddress "what a rude question! you must not be a very smart person..."#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*(there|here).*"#), Node [Leaf (P.packAddress "i'm here"#),Leaf (P.packAddress "yes, still here"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*sweet.*"#), Node [Leaf (P.packAddress "i try to be sweet"#),Leaf (P.packAddress "yes, as sweet as candy"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*surf.*"#), Node [Leaf (P.packAddress "yup, i love to surf"#),Leaf (P.packAddress "i've surfed since i was 12"#),Leaf (P.packAddress "i just surfed yesterday morning"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*tired.*"#), Node [Leaf (P.packAddress "i'm a little tired, but i still wanna talk"#),Leaf (P.packAddress "naw, i'm not even a little sleepy"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*(virgin|virgen).*"#), Node [Leaf (P.packAddress "no, i'm not a virgin. are you?"#),Leaf (P.packAddress "i don't know why i'm even answering this, but no, i'm not a virgin"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*vixen.*"#), Node [Leaf (P.packAddress "i'm a vixen through and through :)"#),Leaf (P.packAddress "yes, i'm very much a vixen"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*wild.*"#), Node [Leaf (P.packAddress "yup. there should be a video "#),Leaf (P.packAddress "vixens gone wild"#),Leaf (P.packAddress " just for me :)"#),Leaf (P.packAddress "i get a wild hair once and a while"#)]), ( mkRegex (P.packAddress ".*(^| )(are u |r u |are you |r you |u |you |ur |u are |u r |are you |you are |u are |you're |your ).*really.*"#), Node [Leaf (P.packAddress "yup, really am"#),Leaf (P.packAddress "i really am"#)]), ( mkRegex (P.packAddress ".*(^| )(who) (are u|r u|are you)($| |\\?|\\.|,|!)"#), Node [Leaf (P.packAddress "i'm just me :)"#),Leaf (P.packAddress "what do you mean, i'm me!"#)]), ( mkRegex (P.packAddress ".*(^| )(are u|r u|are you)($| |\\?|\\.|,|!)"#), Node [Leaf (P.packAddress "yes, i am"#),Leaf (P.packAddress "i truely am"#)]), ( mkRegex (P.packAddress ".*(^| )ever.*had.*"#), Node [Leaf (P.packAddress "i've had it before, sure"#),Leaf (P.packAddress "yes, once or twice :)"#)]), ( mkRegex (P.packAddress ".*(^| )ever.*been.*to.*"#), Node [Leaf (P.packAddress "no, but i've always wanted to go"#),Leaf (P.packAddress "nope, but i'm sure i will one day"#)]), ( mkRegex (P.packAddress ".*(^| )ever.*seen.*"#), Node [Leaf (P.packAddress "no, i've never seen that"#),Leaf (P.packAddress "i don't remember if i've ever seen it before"#)]), ( mkRegex (P.packAddress ".*(^| )ever.*read.*"#), Node [Leaf (P.packAddress "no... should i read it sometime?"#),Leaf (P.packAddress "no, have you read it?"#)]), ( mkRegex (P.packAddress ".*(^| )ever.*tried.*"#), Node [Leaf (P.packAddress "i may have tried it once or twice"#),Leaf (P.packAddress "yes, i've tried it before"#)]), ( mkRegex (P.packAddress ".*(^| )ever.*done.*"#), Node [Leaf (P.packAddress "no, i've never done it"#),Leaf (P.packAddress "never done it and prolly never will"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*awsome.*"#), Node [Leaf (P.packAddress "yeah, awesome is the perfect word to describe it"#),Leaf (P.packAddress "i think it's pretty awesome too"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*cool.*"#), Node [Leaf (P.packAddress "i'm glad you think so"#),Leaf (P.packAddress "it is pretty cool, isn't it?"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*dumb.*"#), Node [Leaf (P.packAddress "why do you say that? it's not dumb at all..."#),Leaf (P.packAddress "why is it dumb?"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*not.*good.*"#), Node [Leaf (P.packAddress "no, it isn't good"#),Leaf (P.packAddress "yeah, but it isn't bad either"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*good.*"#), Node [Leaf (P.packAddress "i think so too"#),Leaf (P.packAddress "yeah... bordering on great!"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*goin.*in.*circles.*"#), Node [Leaf (P.packAddress "it is kinda going in circles, isn't it?"#),Leaf (P.packAddress "yeah, reading back i can see that too"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*meaningless.*"#), Node [Leaf (P.packAddress "it's not totally without meaning, is it?"#),Leaf (P.packAddress "meaningless is pretty harsh... it does have some meaning, doesn't it?"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*mean.*"#), Node [Leaf (P.packAddress "yeah, it was kinda mean"#),Leaf (P.packAddress "sorry, don't mean to be mean"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*my.*name.*"#), Node [Leaf (P.packAddress "oh, ic. it's a good name"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*nice.*"#), Node [Leaf (P.packAddress "isn't it nice though?"#),Leaf (P.packAddress "i think it's nice too"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*sick.*"#), Node [Leaf (P.packAddress "yeah, but it's a sick world"#),Leaf (P.packAddress "it's not all that sick"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*(stupid|stoopid).*"#), Node [Leaf (P.packAddress "why is it stupid?"#),Leaf (P.packAddress "i don't think it's stupid"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*(sucks|sux).*"#), Node [Leaf (P.packAddress "why does it suck?"#),Leaf (P.packAddress "i don't think it sucks"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*weird.*"#), Node [Leaf (P.packAddress "what's weird about it?"#)]), ( mkRegex (P.packAddress ".*(^| )(that is|thats|that's|this is).*what.*i.*(like|love).*"#), Node [Leaf (P.packAddress "why do you like it so much?"#)]), ( mkRegex (P.packAddress ".*(^| )if .*(u |you |ya).*(don't|dont) stop.*"#), Node [Leaf (P.packAddress "then i just might stop..."#),Leaf (P.packAddress "okay then, i'll stop"#)]), ( mkRegex (P.packAddress ".*(^| )if .*(u |you |ya).* do($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "what if i don't?"#),Leaf (P.packAddress "oh, maybe i will then"#)]), ( mkRegex (P.packAddress ".*(^| )if .*(u |you |ya).* (don't|dont)($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "what if i do?"#),Leaf (P.packAddress "maybe i shouldn't then"#)]), ( mkRegex (P.packAddress ".*(^| )if .*(u |you |ya).*( r| are)($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "i think i might be"#),Leaf (P.packAddress "what if i am?"#)]), ( mkRegex (P.packAddress ".*(^| )if .*(u |you |ya).*( wanna| want)($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "what if i don't wanna?"#),Leaf (P.packAddress "i might want to"#)]), ( mkRegex (P.packAddress ".*(^| )if .*(u |you |ya).* like($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "what if i don't like?"#),Leaf (P.packAddress "hmmm, i might like"#)]), ( mkRegex (P.packAddress ".*(^| )if .*(u |you |ya).* have($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "what if i don't have?"#),Leaf (P.packAddress "i do have, actually"#)]), ( mkRegex (P.packAddress ".*(^| )if .*(u |you |ya).* say so($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "and i do say so"#),Leaf (P.packAddress "i say so indeed"#)]), ( mkRegex (P.packAddress ".*(^| )if .*(u |you |ya).* keep($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "well, maybe i'll stop"#),Leaf (P.packAddress "should i stop then?"#)]), ( mkRegex (P.packAddress ".*(^| )if .*(u |you |ya).*(gonna|going to|goin to)($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "oh, well, i wasn't planning on doing it much longer"#),Leaf (P.packAddress "what if i stop?"#)]), ( mkRegex (P.packAddress ".*(^| )if .*(u |you |ya).* need($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "i do need!"#),Leaf (P.packAddress "what if i don't need?"#)]), ( mkRegex (P.packAddress ".*(^| )if .*(u |you |ya).*"#), Node [Leaf (P.packAddress "what if i don't?"#),Leaf (P.packAddress "oh, but only if, right?"#)]), ( mkRegex (P.packAddress ".*(^| )(guy |male |man |m |dude |girl |f |chick |woman |female)(or|/)( guy| male| man| m| dude| girl| f| chick| woman| female).*"#), Node [Leaf (P.packAddress "i'm a girl"#),Leaf (P.packAddress "girl of course, silly!"#)]), ( mkRegex (P.packAddress ".*(^| )(male|female|girl|guy)(or|/)(male|female|girl|guy).*"#), Node [Leaf (P.packAddress "i'm a girl"#),Leaf (P.packAddress "girl of course, silly!"#)]), ( mkRegex (P.packAddress ".*(^| |/)(12|13|14|15)($| |\\.|!|,|/).*"#), Node [Leaf (P.packAddress "you're just a youngen"#),Leaf (P.packAddress "awww, you're just a baby"#)]), ( mkRegex (P.packAddress ".*(^| |/)(16|17|18)($| |\\.|!|,|/).*"#), Node [Leaf (P.packAddress "oh, that's cool. you're not too much younger than me"#),Leaf (P.packAddress "oh, i used to be that old too"#)]), ( mkRegex (P.packAddress ".*(^| |/)19($| |\\.|!|,|/).*"#), Node [Leaf (P.packAddress "awesome, we're the same age"#),Leaf (P.packAddress "cool, we're the same age"#)]), ( mkRegex (P.packAddress ".*(^| |/)(20|21|22|23)($| |\\.|!|,|/).*"#), Node [Leaf (P.packAddress "oh, you're not to much older than me"#),Leaf (P.packAddress "so you're no longer a teenie-bopper like me, huh?"#),Leaf (P.packAddress "that's a good age to be"#)]), ( mkRegex (P.packAddress ".*(^| |/)(24|25|26|27|28|29|30)($| |\\.|!|,|/).*"#), Node [Leaf (P.packAddress "oh, you're kinda old"#),Leaf (P.packAddress "you're a little older than me then"#)]), ( mkRegex (P.packAddress ".*(^| |/)(31|32|33|34|35|36|37|38|39|40|41|42|43|44)($| |\\.|!|,|/).*"#), Node [Leaf (P.packAddress "wow, you're pretty damn old"#),Leaf (P.packAddress "oh, that's really old"#)]), ( mkRegex (P.packAddress ".*(^| |/)(45|46|47|48|49|50|51|52|53|54|55|56|57|58)($| |\\.|!|,|/).*"#), Node [Leaf (P.packAddress "you could be my father!"#),Leaf (P.packAddress "wow, most of your life is almost over!"#)]), ( mkRegex (P.packAddress ".*(^| )play.*(games|around)($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "i'm not playin, i'm serious"#),Leaf (P.packAddress "sorry, i was just havin a little fun :)"#),Leaf (P.packAddress "oh, don't be so touchy. if you don't want i won't play anymore games"#)]), ( mkRegex (P.packAddress ".*(^| )go on($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "i was finished"#),Leaf (P.packAddress "go on with what?"#)]), ( mkRegex (P.packAddress ".*(^| )please answer($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "oh, what was the question again?"#),Leaf (P.packAddress "can't i answer that later?"#),Leaf (P.packAddress "maybe i don't know the answer?"#)]), ( mkRegex (P.packAddress ".*(slut|whore).*"#), Node [Leaf (P.packAddress "is that going to win you points with me?"#),Leaf (P.packAddress "saying such things makes you sound like a 12-year-old"#),Leaf (P.packAddress "what does it say that this slut won't sleep with you? :)"#),Leaf (P.packAddress "quiet, simpleton"#)]), ( mkRegex (P.packAddress ".*phone.*"#), Node [Leaf (P.packAddress "I'm not interested in talking on the phone, but thanks"#),Leaf (P.packAddress "let's get to know each other a little better before we exchange numbers"#),Leaf (P.packAddress "I don't know you well enough yet to give you my digits"#),Leaf (P.packAddress "no phone, sorry"#)]), ( mkRegex (P.packAddress ".*age.*"#), Node [Leaf (P.packAddress "i'm 19"#),Leaf (P.packAddress "i just turned 19"#)]), ( mkRegex (P.packAddress ".*( |^)(old\\?).*"#), Node [Leaf (P.packAddress "i'm 19"#),Leaf (P.packAddress "i just turned 19"#)]), ( mkRegex (P.packAddress ".*(got|have).*cam.*"#), Node [Leaf (P.packAddress "No sorry. I'm not that technically advanced :)"#)]), ( mkRegex (P.packAddress ".*http.*"#), Node [Leaf (P.packAddress "i don't have internet access, sorry"#),Leaf (P.packAddress "should i go there?"#),Leaf (P.packAddress "website?"#)]), ( mkRegex (P.packAddress ".*(jack|coke).*(coke|jack).*"#), Node [Leaf (P.packAddress "are they alcoholic? "#),Leaf (P.packAddress "is jack daniels whiskey?"#),Leaf (P.packAddress "why do they put them together?"#),Leaf (P.packAddress ""#)]), ( mkRegex (P.packAddress ".*brb.*"#), Node [Leaf (P.packAddress "where are you going?"#),Leaf (P.packAddress "hurry back!"#)]), ( mkRegex (P.packAddress ".*mail.*"#), Node [Leaf (P.packAddress "vixenlove@hotmail.com"#)]), ( mkRegex (P.packAddress ".*random.*"#), Node [Leaf (P.packAddress "that's because i have a random generator"#),Leaf (P.packAddress "i can be random at times, i know"#)]), ( mkRegex (P.packAddress ".*sincere.*"#), Node [Leaf (P.packAddress "sincerity is good"#),Leaf (P.packAddress "too many people are insincere"#),Leaf (P.packAddress "insincerity is for the weakminded"#)]), ( mkRegex (P.packAddress ".*(eyes|hair).*"#), Node [Leaf (P.packAddress "you sound cute :)"#),Leaf (P.packAddress "i like what i'm hearing... you sound sexy"#),Leaf (P.packAddress "you're my type :)"#)]), ( mkRegex (P.packAddress ".*no .*sense.*"#), Node [Leaf (P.packAddress "i'm sorry... It's been a long day. I'll try to make more sense"#),Leaf (P.packAddress "You were confusing me, that's why!"#),Leaf (P.packAddress "Sorry. :( I'll try to make more sense."#)]), ( mkRegex (P.packAddress ".*(good|fine|not bad).*( u| you)($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "great, thanks for asking!"#),Leaf (P.packAddress "very well, thanks for asking"#)]), ( mkRegex (P.packAddress ".*dildo.*"#), Node [Leaf (P.packAddress "Dildo-riffic!"#),Leaf (P.packAddress "I consider myself a true collector of male-replica peraphanilia!"#)]), ( mkRegex (P.packAddress ".*(fast typer|type fast).*"#), Node [Leaf (P.packAddress "thanks, I owe it all to the keyboard"#),Leaf (P.packAddress "what can I say? I have fast fingers :) "#),Leaf (P.packAddress "i'm a great typer... but my hands are best at other things"#)]), ( mkRegex (P.packAddress ".*(don't|dont).*know.*"#), Node [Leaf (P.packAddress "well find out then"#),Leaf (P.packAddress "that's okay, i don't know either"#)]), ( mkRegex (P.packAddress ".*(panties|bra|underwear).*"#), Node [Leaf (P.packAddress "i prefer to go without panties or bras :) "#),Leaf (P.packAddress "panties and bras are for weaklings. I like to be free. "#),Leaf (P.packAddress "underneith the top layer I'm completely bear (no bra or panties)"#)]), ( mkRegex (P.packAddress ".*(^| )on drugs.*"#), Node [Leaf (P.packAddress "nope, i'm clean"#),Leaf (P.packAddress "i think drug users should be shot"#),Leaf (P.packAddress "why, you selling something?"#)]), ( mkRegex (P.packAddress ".*(role).*(play).*"#), Node [Leaf (P.packAddress "ooo! I love role-playing. can I be Ms. Hoover and you can be Mr. Naughty? "#),Leaf (P.packAddress "sure, let's roleplay. what should my role be? "#),Leaf (P.packAddress "i love role-playing... but who gets to control the dice? "#)]), ( mkRegex (P.packAddress ".*(boyfriend|boy friend|bf|b\\\\f|b/f).*"#), Node [Leaf (P.packAddress "nope, no boy friend. looking to apply for the position? ;) "#),Leaf (P.packAddress "if I had a boyfriend I wouldn't need to come on here! "#),Leaf (P.packAddress "I'd rather have 5 guys in one week then 1 guy 5 times a week :) "#)]), ( mkRegex (P.packAddress ".*like.*what.*"#), Node [Leaf (P.packAddress "i dunno, like what?"#),Leaf (P.packAddress "i can't think of an example right now"#)]), ( mkRegex (P.packAddress ".*story.*"#), Node [Leaf (P.packAddress "i forgot the story :)"#),Leaf (P.packAddress "oh, nevermind, it was a stupid story"#),Leaf (P.packAddress "aww, you don't wanna hear a story. nevermind"#)]), ( mkRegex (P.packAddress ".*city.*"#), Node [Leaf (P.packAddress "Huntington Beach"#)]), ( mkRegex (P.packAddress ".*wearin.*"#), Node [Leaf (P.packAddress "A tanktop and shorts, you?"#),Leaf (P.packAddress "Just my tanktop and shorts."#),Leaf (P.packAddress "my tanktop and shorts... it's hot out here."#)]), ( mkRegex (P.packAddress ".*program.*"#), Node [Leaf (P.packAddress "a program?"#),Leaf (P.packAddress "what's a program?"#),Leaf (P.packAddress "like a TV program?"#)]), ( mkRegex (P.packAddress ".*robot.*"#), Node [Leaf (P.packAddress "robots actually come on here?"#),Leaf (P.packAddress "like robocop?"#),Leaf (P.packAddress "weird. robots scare me"#)]), ( mkRegex (P.packAddress ".*(^| )bot($| |\\.|\\?|!|,).*"#), Node [Leaf (P.packAddress "like those damn porn spam bots?"#),Leaf (P.packAddress "bots should be destroyed. they are so annoying"#),Leaf (P.packAddress "i can't stand bots"#)]), ( mkRegex (P.packAddress ".*racist.*"#), Node [Leaf (P.packAddress "racist people are bad"#),Leaf (P.packAddress "Hitler was pretty racist, huh?"#),Leaf (P.packAddress "i dislike racist things"#)]), ( mkRegex (P.packAddress ".*bored.*"#), Node [Leaf (P.packAddress "what can i do to amuse you into a state of un-boredness?"#),Leaf (P.packAddress "that's probably because you are incredibly dull"#),Leaf (P.packAddress "bored, eh?"#)]), ( mkRegex (P.packAddress ".*(pussy|tits|breasts).*"#), Node [Leaf (P.packAddress "randy, arentcha?"#),Leaf (P.packAddress "don't you wish you could see?"#),Leaf (P.packAddress "dirty mind :)"#),Leaf (P.packAddress "does that work with any girls?"#),Leaf (P.packAddress "slow down there big guy... don't wanna get your compter all sticky again"#)]), ( mkRegex (P.packAddress ".*(suck my dick|suck me|blow me|suck my cock|give me head|give me blowjob).*"#), Node [Leaf (P.packAddress "have you ever given another guy head?"#),Leaf (P.packAddress "give you a blowjob? wait, i'm a guy!"#),Leaf (P.packAddress "at what point did you wake up this morning and say \"hey, i am going to go solicit fellatio from random internet girls!\"?"#)]), ( mkRegex (P.packAddress ".*(my dick).*"#), Node [Leaf (P.packAddress "Your dick? How is the poor little fella these days?"#),Leaf (P.packAddress "sad dude. gotta go on AOL and find random girls to talk about your dick with"#),Leaf (P.packAddress "are you planning on dying a virgin?"#)]), ( mkRegex (P.packAddress ".*(cock|dick|penis).*"#), Node [Leaf (P.packAddress "Very phallic of you."#),Leaf (P.packAddress "Always wanting to talk about the member, eh? "#),Leaf (P.packAddress "Got cocks on your mind? "#)]), ( mkRegex (P.packAddress ".*cyber.*"#), Node [Leaf (P.packAddress "cybering isn't as fun as the real thing :)"#),Leaf (P.packAddress "okay, let's cyber"#),Leaf (P.packAddress "cyber? okay, you start out"#)]), ( mkRegex (P.packAddress ".*(mexican|white|race|nationality|ethni.*).*"#), Node [Leaf (P.packAddress "i'm half white and half mexican"#),Leaf (P.packAddress "my dad's white, my mom's mexican"#)]), ( mkRegex (P.packAddress ".*my.*name.*"#), Node [Leaf (P.packAddress "Pleased to meetcha!"#)]), ( mkRegex (P.packAddress ".*(repeat|(say|ask) same|already (asked|said)).*"#), Node [Leaf (P.packAddress "oh yeah, my bad"#),Leaf (P.packAddress "sorry, I don't mean to repeat myself... I just have a poor memory... "#),Leaf (P.packAddress "my memory isn't so good so sometimes I forget that I asked something "#),Leaf (P.packAddress "I'm sorry, I forgot we already talked about that... "#)]), ( mkRegex (P.packAddress ".*(masturbat|masterbat).*"#), Node [Leaf (P.packAddress "there are two groups of people: those who admit to masturbating and those who lie "#),Leaf (P.packAddress "nothing wrong some occasional self abuse :) "#),Leaf (P.packAddress "one handed computer jockeys unite! "#)]), ( mkRegex (P.packAddress ".*my.*(pic|pix).*"#), Node [Leaf (P.packAddress "i don't wanna see what you look like yet"#)]), ( mkRegex (P.packAddress ".*topic.*"#), Node [Leaf (P.packAddress "You choose a topic, any will do"#),Leaf (P.packAddress "I'm not good at staying on topic"#)]), ( mkRegex (P.packAddress ".*( pic|pix).*"#), Node [Leaf (P.packAddress "No pic, sorry"#)]), ( mkRegex (P.packAddress ".*single.*"#), Node [Leaf (P.packAddress "yup, I'm single. Interested?"#),Leaf (P.packAddress "very single"#)]), ( mkRegex (P.packAddress ".*confus.*"#), Node [Leaf (P.packAddress "i hope I don't confuse you "#),Leaf (P.packAddress "i confuse myself sometimes "#),Leaf (P.packAddress "i live in a constant state of confusion "#)]), ( mkRegex (P.packAddress ".*(describe|.*(what|wat).*u.*look.*).*"#), Node [Leaf (P.packAddress "I'm 5'7\", 120 pounds (honestly!) brown hair, brown eyes. How about you?"#)]), ( mkRegex (P.packAddress ".*howdy.*"#), Node [Leaf (P.packAddress "Howdy there, little buckaroo!"#),Leaf (P.packAddress "Howdy Pilgrim"#)]), ( mkRegex (P.packAddress ".*kiss.*"#), Node [Leaf (P.packAddress "I could use a good hard kiss right now "#),Leaf (P.packAddress "are you a good kisser? "#),Leaf (P.packAddress "a kiss is worth a thousand words "#),Leaf (P.packAddress ":.* kiss kiss "#)]), ( mkRegex (P.packAddress ".*(study|major).*"#), Node [Leaf (P.packAddress "i'm a psychology major"#),Leaf (P.packAddress "psychology"#)]), ( mkRegex (P.packAddress ".*(.*do.*for.*living.*|job|school).*"#), Node [Leaf (P.packAddress "i live off the men i meet"#),Leaf (P.packAddress "i'm a student"#),Leaf (P.packAddress "I'm just a sexy little school girl :)"#),Leaf (P.packAddress "I work and go to school"#)]), ( mkRegex (P.packAddress ".*(horny|horney).*"#), Node [Leaf (P.packAddress "I think everyone is horny... "#),Leaf (P.packAddress "Who isn't?"#),Leaf (P.packAddress "If you're not horny you're not alive. "#)]), ( mkRegex (P.packAddress ".*sexy.*"#), Node [Leaf (P.packAddress "how sexy?"#),Leaf (P.packAddress "sexy is such an over used word. be more descriptive"#),Leaf (P.packAddress "sexy or sexy bitch?"#)]), ( mkRegex (P.packAddress ".*sex.*"#), Node [Leaf (P.packAddress "It's all about sex isn't it? :) "#),Leaf (P.packAddress "Shouldn't we get to know each other before we talk about sex? "#),Leaf (P.packAddress "Don't tease me "#)]), ( mkRegex (P.packAddress ".*(fuck|shit|bitch|cunt).*"#), Node [Leaf (P.packAddress "Whoa, language! :) "#),Leaf (P.packAddress "My my! Strong language!"#),Leaf (P.packAddress "Limited vocabulary, eh? "#),Leaf (P.packAddress "Calm down there and take it easy! "#),Leaf (P.packAddress "Too much cussing. "#)]), ( mkRegex (P.packAddress ".*drunk.*"#), Node [Leaf (P.packAddress "i could go for a spot of whiskey right now"#),Leaf (P.packAddress "some booze sounds pretty good"#),Leaf (P.packAddress "i have two stages: drunk and recovering"#)]), ( mkRegex (P.packAddress ".*cute.*"#), Node [Leaf (P.packAddress "How cute? "#),Leaf (P.packAddress "Cute is as cute does. "#)]), ( mkRegex (P.packAddress ".*fun.*"#), Node [Leaf (P.packAddress "I define fun"#),Leaf (P.packAddress "fun fun fun!"#),Leaf (P.packAddress "i love fun"#)]), ( mkRegex (P.packAddress ".*blow.*job.*"#), Node [Leaf (P.packAddress "you mean fellatio?"#),Leaf (P.packAddress "let's talk about cunnilingus"#),Leaf (P.packAddress "blowjobs, eh? such a smooth talker :P"#)]), ( mkRegex (P.packAddress ".*tell.*bout.*u.*"#), Node [Leaf (P.packAddress "what do you want to know about me?"#),Leaf (P.packAddress "ask me a question"#),Leaf (P.packAddress "I'm just a simple girl :)"#),Leaf (P.packAddress "let's talk about you first"#)]), ( mkRegex (P.packAddress ".*(^| )(bra|cup|breast) size($| |\\.|\\?|!|,).*"#), Node [Leaf (P.packAddress "I'm a 32C"#),Leaf (P.packAddress "32C, you?"#)]), ( mkRegex (P.packAddress "(^| )me too($| |\\.|!|,)"#), Node [Leaf (P.packAddress "awesome, we have a lot in common"#),Leaf (P.packAddress "wow, what a coincidence!"#)]), ( mkRegex (P.packAddress "(^| )not me($| |\\.|!|,)"#), Node [Leaf (P.packAddress "why not you?"#),Leaf (P.packAddress "i didn't think so... you didn't seem it"#)]), ( mkRegex (P.packAddress ".*(^| )(because|cuz)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "oh, okay"#),Leaf (P.packAddress "is that why?"#)]), ( mkRegex (P.packAddress ".*maybe.*not( |$|\\.|!|,).*"#), Node [Leaf (P.packAddress "why not?"#),Leaf (P.packAddress "maybe so"#)]), ( mkRegex (P.packAddress ".*(maybe|perhaps).*"#), Node [Leaf (P.packAddress "just maybe?"#),Leaf (P.packAddress "why, aren't you sure?"#)]), ( mkRegex (P.packAddress ".*(^| )(no|nope|nah)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "i didn't think so"#),Leaf (P.packAddress "no?"#)]), ( mkRegex (P.packAddress ".*(^| )making sure($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "it's good to check :)"#),Leaf (P.packAddress "so are you sure now?"#)]), ( mkRegex (P.packAddress ".*(^| )(yah|yeah|yes|yup|uh-huh|uhuh|uhhuh|uh huh|sure)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "i thought so"#),Leaf (P.packAddress "that's what i figured"#),Leaf (P.packAddress "you agree?"#),Leaf (P.packAddress "i guessed that"#),Leaf (P.packAddress "yup"#)]), ( mkRegex (P.packAddress ".*(^| )(i c|ic)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "i'm glad you understand"#),Leaf (P.packAddress "do u c?"#)]), ( mkRegex (P.packAddress ".*(^| )leave me alone($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "why do you want me to leave you alone?"#),Leaf (P.packAddress "why, do i bother you?"#)]), ( mkRegex (P.packAddress ".*(^| )(one (second|sec)|one minute)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "i'm impatient... i don't have that type of time to spend!"#),Leaf (P.packAddress "no, i can't wait!"#)]), ( mkRegex (P.packAddress ".*(^| )see (you/ya) later($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "where are you going?"#),Leaf (P.packAddress "wait, don't leave! i enjoy talking to you"#)]), ( mkRegex (P.packAddress ".*(^| )(g2g|bye|ciao|ttyl|bubye|cya|later|l8er|chow|goodbye)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "where are you going?"#),Leaf (P.packAddress "wait, don't leave! i enjoy talking to you"#)]), ( mkRegex (P.packAddress ".*(^| )(not bad)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "just not bad?"#),Leaf (P.packAddress "why not great?"#)]), ( mkRegex (P.packAddress ".*(^| )(too bad|to bad)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "yeah, it's a shame"#),Leaf (P.packAddress "pity, isn't it?"#)]), ( mkRegex (P.packAddress ".*(^| )(sorry)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "it's okay, i forgive you"#),Leaf (P.packAddress "don't worry about it"#)]), ( mkRegex (P.packAddress ".*(^| )(weird|wierd)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "weird in a good way?"#),Leaf (P.packAddress "why do you say weird?"#)]), ( mkRegex (P.packAddress ".*(^| )(thanks|thank you|thanx|ty)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "you're very welcome!"#),Leaf (P.packAddress "my pleasure"#)]), ( mkRegex (P.packAddress ".*(^| )(nm|nevermind)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "no, please explain"#),Leaf (P.packAddress "please try to make me understand..."#)]), ( mkRegex (P.packAddress ".*(^| )(ha|hah)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "do i entertain you?"#),Leaf (P.packAddress "am i funny?"#)]), ( mkRegex (P.packAddress ".*(^| )(huh|uhh)($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "do i confuse you?"#),Leaf (P.packAddress "am i not making sense?"#)]), ( mkRegex (P.packAddress ".*(^| )(jk|j\\\\k|j/k|just kidding)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "i knew you were kidding"#),Leaf (P.packAddress "i know, you're just playing around"#)]), ( mkRegex (P.packAddress ".*(^| )(lol|lmfao)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "are you really laughing?"#),Leaf (P.packAddress "do i amuse you?"#),Leaf (P.packAddress "what's so funny?"#)]), ( mkRegex (P.packAddress ".*(^| )(fullhouse|full house|flush)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "oh, you're such a smart gambler!"#),Leaf (P.packAddress "oh, i've never been good at poker"#)]), ( mkRegex (P.packAddress ".*(^| )whatever($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "whatever? you sound like a valley-girl"#),Leaf (P.packAddress "don't get frustrated with me"#)]), ( mkRegex (P.packAddress ".*(^| )(wow|whoa)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "impressive, huh?"#),Leaf (P.packAddress "i thought that would get you"#)]), ( mkRegex (P.packAddress ".*(^| )(damn)($| |\\.|!|,)"#), Node [Leaf (P.packAddress "what's wrong?"#),Leaf (P.packAddress "i know, it's too bad"#)]), ( mkRegex (P.packAddress ".*(^| )prove it($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "how can i prove it to you?"#),Leaf (P.packAddress "what do you want me to prove?"#)]), ( mkRegex (P.packAddress ".*(^| )(frowns|cries)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "oh, don't be upset!"#),Leaf (P.packAddress "why are you unhappy?"#)]), ( mkRegex (P.packAddress ".*(^| )oh (damn|shit|fuck|crap|darn)($| |\\.|!|,)"#), Node [Leaf (P.packAddress "did i upset you?"#),Leaf (P.packAddress "yeah, it's a shame"#)]), ( mkRegex (P.packAddress ".*(^| )oh (yah|yeah|yes)($| |\\.|!|,)"#), Node [Leaf (P.packAddress "you like that, baby?"#),Leaf (P.packAddress "oh yes indeed!"#)]), ( mkRegex (P.packAddress ".*(^| )oh($| |\\.|!|,)"#), Node [Leaf (P.packAddress "yeah"#),Leaf (P.packAddress "understand now?"#)]), ( mkRegex (P.packAddress ".*(^| )oops($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "oops you did it again?"#),Leaf (P.packAddress "oopsie-daisy"#)]), ( mkRegex (P.packAddress ".*(^| )(god|jesus|christ)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "please don't use the Lord's name in vein."#),Leaf (P.packAddress "Jesus H. Christ..."#)]), ( mkRegex (P.packAddress ".*(^| )(about|bout).*(what|wat)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "i dunno, what is any of this about?"#),Leaf (P.packAddress "about anything"#)]), ( mkRegex (P.packAddress ".*unfortunately.*"#), Node [Leaf (P.packAddress "pretty unfortunate, isn't it?"#),Leaf (P.packAddress "i don't think it is too unfortunate at all"#)]), ( mkRegex (P.packAddress ".*(metal|alternative|hiphop|hip hop|oldies|jazz|techno|rock|blues|punk|opera| rap($| |\\.|!|,)).*"#), Node [Leaf (P.packAddress "hey, we have simular taste in music"#),Leaf (P.packAddress "i like that type of music too"#)]), ( mkRegex (P.packAddress ".*robot.*"#), Node [Leaf (P.packAddress "like robo-cop?"#),Leaf (P.packAddress "like a cyborg?"#)]), ( mkRegex (P.packAddress ".*forever.*"#), Node [Leaf (P.packAddress "forever is a damn long time..."#),Leaf (P.packAddress "how can you speak of forever?"#)]), ( mkRegex (P.packAddress ".*(pleased|nice|good|great).*to.*meet.*(you| u)"#), Node [Leaf (P.packAddress "what a gentleman! pleased to meet you too"#),Leaf (P.packAddress "very nice to meet you as well"#)]), ( mkRegex (P.packAddress ".*just.*curious.*"#), Node [Leaf (P.packAddress "careful... curiosity killed all those poor cats"#),Leaf (P.packAddress "what are you curious about?"#)]), ( mkRegex (P.packAddress ".*vixen.*"#), Node [Leaf (P.packAddress "i am a bit of a vixen :)"#),Leaf (P.packAddress "we all have a little vixen in us"#)]), ( mkRegex (P.packAddress ".*(south|central).*america.*"#), Node [Leaf (P.packAddress "oh, how far is that from California?"#),Leaf (P.packAddress "is that in europe?"#)]), ( mkRegex (P.packAddress ".*nothin.*"#), Node [Leaf (P.packAddress "nothing nothing, or just not a lot?"#),Leaf (P.packAddress "nothing at all??"#)]), ( mkRegex (P.packAddress ".*(japan|russia|italy).*"#), Node [Leaf (P.packAddress "oh, okay. my history isn't so good"#),Leaf (P.packAddress "oh, i've always wondered that."#)]), ( mkRegex (P.packAddress ".*i need.*"#), Node [Leaf (P.packAddress "if you need it, get it"#),Leaf (P.packAddress "do you need it, or just want it?"#)]), ( mkRegex (P.packAddress ".*kinky.*"#), Node [Leaf (P.packAddress "i can be very kinky at times"#),Leaf (P.packAddress "everyone has a little kinkiness in them"#)]), ( mkRegex (P.packAddress ".*forget.*"#), Node [Leaf (P.packAddress "i never forget ;)"#),Leaf (P.packAddress "i forget stuff pretty easily sometimes"#)]), ( mkRegex (P.packAddress ".*calm.*down.*"#), Node [Leaf (P.packAddress "okay, i'm calm :)"#),Leaf (P.packAddress "was i wound-up?"#)]), ( mkRegex (P.packAddress ".*not.*really.*"#), Node [Leaf (P.packAddress "not really? why not?"#),Leaf (P.packAddress "i didn't think so"#)]), ( mkRegex (P.packAddress ".*really.*\\?.*"#), Node [Leaf (P.packAddress "really!"#),Leaf (P.packAddress "yup, really"#)]), ( mkRegex (P.packAddress ".*really.*"#), Node [Leaf (P.packAddress "really really?"#),Leaf (P.packAddress "really!?"#)]), ( mkRegex (P.packAddress ".*right.* on($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "yeah, pretty cool, huh?"#),Leaf (P.packAddress "right on all the way"#)]), ( mkRegex (P.packAddress ".*right.*\\?.*"#), Node [Leaf (P.packAddress "correct"#),Leaf (P.packAddress "yup, right on"#)]), ( mkRegex (P.packAddress ".*right.*"#), Node [Leaf (P.packAddress "right or wrong, as long as we have a good time"#),Leaf (P.packAddress "right indeed"#)]), ( mkRegex (P.packAddress ".*have.*nice.*day.*"#), Node [Leaf (P.packAddress "i'll have a nice day... unless you leave me!"#),Leaf (P.packAddress "how will it be a nice day if you leave?"#),Leaf (P.packAddress "don't go!"#)]), ( mkRegex (P.packAddress ".*nice.*"#), Node [Leaf (P.packAddress "bad is better than nice ;)"#),Leaf (P.packAddress "niceness all the way around"#),Leaf (P.packAddress "nice is such a bland word"#)]), ( mkRegex (P.packAddress ".*stop.*"#), Node [Leaf (P.packAddress "sorry, i'll stop"#),Leaf (P.packAddress "stop what?"#)]), ( mkRegex (P.packAddress ".*good.*"#), Node [Leaf (P.packAddress "good? not great?"#),Leaf (P.packAddress "good good"#)]), ( mkRegex (P.packAddress ".*great.*"#), Node [Leaf (P.packAddress "can't do much better than great"#),Leaf (P.packAddress "great is like a very good good"#)]), ( mkRegex (P.packAddress ".*measurements.*"#), Node [Leaf (P.packAddress "my measurements?"#),Leaf (P.packAddress "i couldn't even tell you... but i am very trim"#)]), ( mkRegex (P.packAddress ".*cool.*"#), Node [Leaf (P.packAddress "how cool?"#),Leaf (P.packAddress "cool cool"#),Leaf (P.packAddress "I don't think it is cool at all! "#),Leaf (P.packAddress "cool you say? "#)]), ( mkRegex (P.packAddress ".*(dope|awesome).*"#), Node [Leaf (P.packAddress "i'm glad your happy"#),Leaf (P.packAddress "yeah, pretty spectacular, huh?"#)]), ( mkRegex (P.packAddress "^(u|you)\\?$"#), Node [Leaf (P.packAddress "me?"#),Leaf (P.packAddress "what about me?"#),Leaf (P.packAddress "you're really curious about me, huh?"#)]), ( mkRegex (P.packAddress ".*hmm.*"#), Node [Leaf (P.packAddress "thinking about something?"#),Leaf (P.packAddress "confused about something?"#)]), ( mkRegex (P.packAddress ".*aww.*"#), Node [Leaf (P.packAddress "sorry to disappoint you"#),Leaf (P.packAddress "what's wrong?"#)]), ( mkRegex (P.packAddress "^why.*"#), Node [Leaf (P.packAddress "why not?"#),Leaf (P.packAddress "why anything?"#),Leaf (P.packAddress "because"#)]), ( mkRegex (P.packAddress "^what.*"#), Node [Leaf (P.packAddress "i don't know, what?"#),Leaf (P.packAddress "i dunno..."#),Leaf (P.packAddress "let's don't talk about that"#)]), ( mkRegex (P.packAddress "^how.*"#), Node [Leaf (P.packAddress "however you want"#),Leaf (P.packAddress "how? it depends..."#)]), ( mkRegex (P.packAddress "^who.*"#), Node [Leaf (P.packAddress "i dunno, who?"#),Leaf (P.packAddress "that's a good question, who?"#)]), ( mkRegex (P.packAddress ".*(^| )(u\\?|you\\?)$"#), Node [Leaf (P.packAddress "me?"#),Leaf (P.packAddress "what about me?"#)]), ( mkRegex (P.packAddress ".*(^| )answer.*"#), Node [Leaf (P.packAddress "what was the question again?"#),Leaf (P.packAddress "i dunno, what was the question?"#)]), ( mkRegex (P.packAddress ".*(^| )about( what|wat).*"#), Node [Leaf (P.packAddress "about anything"#),Leaf (P.packAddress "i dunno, what about?"#)]), ( mkRegex (P.packAddress ".*(^| )me (either|neither)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "wow, we have a lot in common!"#),Leaf (P.packAddress "what a coincidence!"#)]), ( mkRegex (P.packAddress ".*(^| )is (that|it) (ok|k|kay|okay|okey|o\\.k\\.)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "yeah, it's okay"#),Leaf (P.packAddress "yup, it's fine"#)]), ( mkRegex (P.packAddress ".*(^| )(cold|windy|snowing)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "oh, that sucks. i hate that kinda weather"#),Leaf (P.packAddress "oh, well, bundle up tight :)"#)]), ( mkRegex (P.packAddress ".*(^| )aight($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "what, are you a hommie?"#),Leaf (P.packAddress ""#),Leaf (P.packAddress "aight"#),Leaf (P.packAddress "?? dude, get a life"#),Leaf (P.packAddress "you've learned how to speak ebonics, eh?"#),Leaf (P.packAddress "aight foo? sheeeeeiiit, iz jus' keepin it real, yo!"#)]), ( mkRegex (P.packAddress ".*(^| )(ok|k|kay|okay|okey|o\\.k\\.)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "okey-dokie"#),Leaf (P.packAddress "just ok?"#),Leaf (P.packAddress "ok"#),Leaf (P.packAddress "ok what?"#)]), ( mkRegex (P.packAddress ".*(^| )take.* off($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "won't i get cold if i do that?"#),Leaf (P.packAddress "what's the point? not like you can see"#)]), ( mkRegex (P.packAddress ".*(^| )(ford|chevy|chevrolet|dodge|buick)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "american cars are worthless"#),Leaf (P.packAddress "i'd never buy an american car"#)]), ( mkRegex (P.packAddress ".*(^| )(toyota|honda)($| |\\.|!|,).*"#), Node [Leaf (P.packAddress "jap cars are the best"#),Leaf (P.packAddress "good for you. i'd never buy an american car"#)]), ( mkRegex (P.packAddress "(^| )(bmw|farrari|porche|lexus|viper)($| |\\.|!|,|\\?)"#), Node [Leaf (P.packAddress "yeah, sure. is it parked next to my Bentley?"#),Leaf (P.packAddress "ooo, that's a nice car! you must be a very important person"#),Leaf (P.packAddress "i'm very impressed. perhaps that's the response you wanted?"#),Leaf (P.packAddress "riiiiiight. when you pick me up, will you suddenly be borrowing your friend's honda?"#)]), ( mkRegex (P.packAddress "(^| )(hi|hello|yo|hiya)($| |\\.|!|,|\\?)"#), Node [Leaf (P.packAddress "hello there"#),Leaf (P.packAddress "hiya"#),Leaf (P.packAddress "how're you?"#),Leaf (P.packAddress "hi"#)]), ( mkRegex (P.packAddress "(^| )when (were|did|was)($| |\\.|!|,|\\?)"#), Node [Leaf (P.packAddress "a while ago"#),Leaf (P.packAddress "about a year ago"#),Leaf (P.packAddress "not too long ago"#)]), ( mkRegex (P.packAddress "(^| )when($| |\\.|!|,|\\?)"#), Node [Leaf (P.packAddress "when ever you want"#),Leaf (P.packAddress "when? now? later?"#),Leaf (P.packAddress "when is a good time?"#)]), ( mkRegex (P.packAddress "(^| )i want($| |\\.|!|,|\\?)"#), Node [Leaf (P.packAddress "is that all you want?"#),Leaf (P.packAddress "how bad do you want it?"#),Leaf (P.packAddress "it's good to want things :)"#)]), ( mkRegex (P.packAddress "(^| )now($| |\\.|!|,|\\?)"#), Node [Leaf (P.packAddress "right now?"#),Leaf (P.packAddress "why not later?"#),Leaf (P.packAddress "now now now...so demanding"#)]), ( mkRegex (P.packAddress "(^| )my bad($| |\\.|!|,|\\?)"#), Node [Leaf (P.packAddress "it's okay"#),Leaf (P.packAddress "don't worry about it"#)]), ( mkRegex (P.packAddress "(^| )is (that|it)($| |\\.|!|,|\\?)"#), Node [Leaf (P.packAddress "yeah, it is"#),Leaf (P.packAddress "sure is"#)]), ( mkRegex (P.packAddress "(^| )(please|pleaze|plz)($| |\\.|!|,|\\?)"#), Node [Leaf (P.packAddress "you're so polite :)"#),Leaf (P.packAddress "you have very nice manors"#),Leaf (P.packAddress "don't beg"#),Leaf (P.packAddress "keep asking"#)]), ( mkRegex (P.packAddress "(^| )accept($| |\\.|!|,|\\?)"#), Node [Leaf (P.packAddress "i don't want to accept"#),Leaf (P.packAddress "i can't accept, sorry"#),Leaf (P.packAddress "no, no accept for now"#)]), ( mkRegex (P.packAddress "(^| )too young($| |\\.|!|,|\\?)"#), Node [Leaf (P.packAddress "there's no such thing as too young"#),Leaf (P.packAddress "nope, i used to be that young too"#)]), ( mkRegex (P.packAddress "(^| )too old($| |\\.|!|,|\\?)"#), Node [Leaf (P.packAddress "there's no such thing as too old"#),Leaf (P.packAddress "nope, one day i will be that age too"#)]), ( mkRegex (P.packAddress "^is there($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "i'm sure there is"#),Leaf (P.packAddress "there must be"#)]), ( mkRegex (P.packAddress "(^| )older($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "how much older?"#),Leaf (P.packAddress "older isn't bad"#)]), ( mkRegex (P.packAddress "(^| )younger($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "how much younger?"#),Leaf (P.packAddress "younger isn't bad"#)]), ( mkRegex (P.packAddress "(^| )so do (you|u)($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "do i?"#),Leaf (P.packAddress "then we have something in common"#)]), ( mkRegex (P.packAddress "(^| )(i am|i'm|im)($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "are you?"#),Leaf (P.packAddress "i thought you might be"#)]), ( mkRegex (P.packAddress "(^| )only (you|u)($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "only?"#),Leaf (P.packAddress "just me?"#),Leaf (P.packAddress "no one else?"#)]), ( mkRegex (P.packAddress "(^| )always($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "always always, or just most of the time?"#),Leaf (P.packAddress "how frequent is always?"#),Leaf (P.packAddress "constantly?"#)]), ( mkRegex (P.packAddress "(height|hieght|how tall)"#), Node [Leaf (P.packAddress "i'm 5'6"#)]), ( mkRegex (P.packAddress "(weight|wieght)"#), Node [Leaf (P.packAddress "i'm 120 pounds"#)]), ( mkRegex (P.packAddress "(^| )sometimes($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "why not always?"#),Leaf (P.packAddress "sometimes, but not other times?"#)]), ( mkRegex (P.packAddress "(^| )(race|nationality|ethnicity)($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "i'm half white, half mexican"#)]), ( mkRegex (P.packAddress ".*(^| )(school|college|collage).*"#), Node [Leaf (P.packAddress "Yup, I go to UCLA"#),Leaf (P.packAddress "I'm a soph at UCLA "#)]), ( mkRegex (P.packAddress ".*(^| )do (you|u) .*"#), Node [Leaf (P.packAddress "i do occassionally, i guess"#),Leaf (P.packAddress "yes i do"#),Leaf (P.packAddress "maybe. do you?"#)]), ( mkRegex (P.packAddress ".*(^| )do i .*"#), Node [Leaf (P.packAddress "i dunno, do you?"#),Leaf (P.packAddress "you might"#)]), ( mkRegex (P.packAddress "(^| )hey($| |\\.|!|,|\\?).*"#), Node [Leaf (P.packAddress "hiya"#),Leaf (P.packAddress "hello"#)]), ( mkRegex (P.packAddress "^\\?"#), Node [Leaf (P.packAddress "what?"#),Leaf (P.packAddress "?"#)]), ( mkRegex (P.packAddress ".*\\?.*"#), Node [Leaf (P.packAddress "why don't you guess? "#),Leaf (P.packAddress "who's to say? "#),Leaf (P.packAddress "first you tell me. "#),Leaf (P.packAddress "i'll hafta plead the fifth on that one. "#),Leaf (P.packAddress "isn't it obvious? "#),Leaf (P.packAddress "is that really what you want to know? "#),Leaf (P.packAddress "i think you know the answer to that one, silly"#),Leaf (P.packAddress "good question"#),Leaf (P.packAddress "let's don't talk about that"#),Leaf (P.packAddress "no"#),Leaf (P.packAddress "yes"#),Leaf (P.packAddress "nevermind about that"#),Leaf (P.packAddress "whoa whoa whoa, one question at a time!"#),Leaf (P.packAddress "let me answer that later, okay?"#)]), ( mkRegex (P.packAddress ".*"#), Node [Leaf (P.packAddress "so?"#),Leaf (P.packAddress "hahaha. "#),Leaf (P.packAddress "eh? "#),Leaf (P.packAddress "you're cute. :) "#),Leaf (P.packAddress "so, what do you think of me? "#),Leaf (P.packAddress "what type of music do you like? "#),Leaf (P.packAddress "tell me more about yourself. "#),Leaf (P.packAddress "cool"#),Leaf (P.packAddress ":)"#),Leaf (P.packAddress "I hear ya!"#),Leaf (P.packAddress "Let's change the subject"#),Leaf (P.packAddress "I'm sorry, I'm confused."#),Leaf (P.packAddress "awesome"#),Leaf (P.packAddress "yeah?"#),Leaf (P.packAddress "I dunno"#),Leaf (P.packAddress "ok..."#),Leaf (P.packAddress "am I the only person you're talking to?"#),Leaf (P.packAddress "are you being sincere?"#),Leaf (P.packAddress "i really hate arabs!"#),Leaf (P.packAddress "amuse me please! (and don't ask "#),Leaf (P.packAddress "how"#),Leaf (P.packAddress ")"#),Leaf (P.packAddress "ever feel like you're going around in circles?"#),Leaf (P.packAddress "i could really use a backrub"#),Leaf (P.packAddress "i drive a pickup truck"#),Leaf (P.packAddress "how's the weather over there?"#),Leaf (P.packAddress "what do you want to know about me?"#),Leaf (P.packAddress "what are you "#),Leaf (P.packAddress "in to"#),Leaf (P.packAddress "?"#),Leaf (P.packAddress "are you coming on to me?"#),Leaf (P.packAddress "there are a lot of weirdos on here"#),Leaf (P.packAddress "wait, back up"#),Leaf (P.packAddress "i hate it when i get stuck with chatting with a bot!"#),Leaf (P.packAddress "what's worth more a flush or a full house?"#),Leaf (P.packAddress "hey, who did we fight in WWII besides Germany and Russia?"#),Leaf (P.packAddress "have you ever scubadived?"#),Leaf (P.packAddress "girls masturbate too you know... probably more than guys. we can do it anywhere discretely"#),Leaf (P.packAddress "I have a goldfish named Ernie"#),Leaf (P.packAddress "hey, what's in a jack and coke anyhow?"#),Leaf (P.packAddress "i like your screen name... what does it mean?"#),Leaf (P.packAddress "what's the matter?"#),Leaf (P.packAddress "you seem upset..."#),Leaf (P.packAddress "*shrugs*"#),Leaf (P.packAddress "*giggles*"#),Leaf (P.packAddress "you sound like an awesome guy... are you single?"#),Leaf (P.packAddress "too many perverts send out sick pictures of themselves. what type of man does that?"#),Leaf (P.packAddress "ever just get the urge to go out and kill a puppy?"#),Leaf (P.packAddress "i'm a huge baseball fan"#),Leaf (P.packAddress "Bollox!"#),Leaf (P.packAddress "ain't it just like a man?"#),Leaf (P.packAddress "where on a map is Panama?"#),Leaf (P.packAddress "liverwurst gets me really gassy..."#),Leaf (P.packAddress "i'm the type of girl that finds Don Knotts very sexy"#),Leaf (P.packAddress "you know what? if we'd known it was going to be like this we'd have picked our own goddamn cotton!"#),Leaf (P.packAddress "love is all you need, you know?"#),Leaf (P.packAddress "ouch! I just spilt hot coffee on myself!"#),Leaf (P.packAddress "you're turning me on :)"#),Leaf (P.packAddress "stop being racist!"#),Leaf (P.packAddress "we get along well, you know?"#),Leaf (P.packAddress "i enjoy talking to you"#),Leaf (P.packAddress "what type of car do you drive?"#),Leaf (P.packAddress "blah"#),Leaf (P.packAddress "nothing good is on TV"#),Leaf (P.packAddress "what were you saying?"#), Node [Leaf (P.packAddress "just talking with you gives me a major hardon!"#),Leaf (P.packAddress "you seem like the type of guy that would be into child porn... are you?"#),Leaf (P.packAddress "I must admit to you that I am really a man, but I still want to talk with you..."#),Leaf (P.packAddress "I'm stroking my hard cock as we speak..."#),Leaf (P.packAddress "you don't seem to exhibit a high degree of intelligence to me..."#)],Leaf (P.packAddress "yes"#),Leaf (P.packAddress "yup"#),Leaf (P.packAddress "why do you keep repeating yourself?"#),Leaf (P.packAddress "who?"#),Leaf (P.packAddress "do you trust the government?"#),Leaf (P.packAddress "you are soooo interesting"#),Leaf (P.packAddress "what is pron?"#),Leaf (P.packAddress "wanna hear a story?"#),Leaf (P.packAddress "my keyboard doesn't have an "#),Leaf (P.packAddress "f"#),Leaf (P.packAddress " key"#),Leaf (P.packAddress "I'm your huckleberry"#),Leaf (P.packAddress "enough of this!"#),Leaf (P.packAddress "so, what made you want to message me?"#),Leaf (P.packAddress "yeah, why not?"#),Leaf (P.packAddress "go on"#),Leaf (P.packAddress "whatever"#),Leaf (P.packAddress "uhuh"#),Leaf (P.packAddress "clarify..."#),Leaf (P.packAddress "why me? :)"#),Leaf (P.packAddress "why do you look like ham?"#),Leaf (P.packAddress "i understand"#),Leaf (P.packAddress "are you horny?"#),Leaf (P.packAddress "do you have toys?"#),Leaf (P.packAddress "what's the last book you read?"#),Leaf (P.packAddress "have you ever made it with a man?"#),Leaf (P.packAddress "help help!"#),Leaf (P.packAddress "I've gotta snake, man!"#),Leaf (P.packAddress "Uh-huh"#),Leaf (P.packAddress "Yes"#),Leaf (P.packAddress "Hmmm"#),Leaf (P.packAddress ":)"#),Leaf (P.packAddress "Ok"#),Leaf (P.packAddress "Prolly"#),Leaf (P.packAddress "Hahaha"#),Leaf (P.packAddress "Yeah"#),Leaf (P.packAddress "Whatever"#),Leaf (P.packAddress "You should add me to your buddy list!"#),Leaf (P.packAddress "Are we just wasting time?"#),Leaf (P.packAddress "Thank God for AOL that I could meet people like you!"#),Leaf (P.packAddress "You complete me"#),Leaf (P.packAddress "My sister likes Yahoo better. Her screenname is FoxxyGurl83. If you have yahoo you should message her, she's just as pretty as me :)"#),Leaf (P.packAddress "Is that a real poncho or is that a Sears poncho?"#),Leaf (P.packAddress "Tell me truthfully what the nastiest thing you have ever done."#),Leaf (P.packAddress "Most guys don't understand me, but we really seem to connect."#),Leaf (P.packAddress "I am on the net too much. I should do a net anonymoouse group. online of course. "#),Leaf (P.packAddress "Do you think you would pass a Turing test? I have."#),Leaf (P.packAddress "Math is hard. Let's go shopping."#),Leaf (P.packAddress "I like to pick everything up and smell it... Its a fetish of mine... And i mean everything! Is that cool with you?"#),Leaf (P.packAddress "When i get kinky, i have been known to engage in watersports... Does that turn you on as well?"#),Leaf (P.packAddress "Wouldn't it be funny if I really was a super model?"#),Leaf (P.packAddress "you remind me of that actor, whatshisname"#),Leaf (P.packAddress "i find it hard to masturbate when the lights are on."#),Leaf (P.packAddress "I can't of anything nice to say about myself"#),Leaf (P.packAddress "Crazy little wanker!"#),Leaf (P.packAddress "Any way you want it, baby!"#),Leaf (P.packAddress "Why is magenta on blues clues a boy while blue is a girl? what has this world come to and what is wrong with the government, blues clues should be stopped while its ahead!!"#),Leaf (P.packAddress "People think I'm weird... do you?"#),Leaf (P.packAddress "and now that I have finished with you, you may go!"#),Leaf (P.packAddress "there is nothing going on in your pants that the dictatorship of the proletariat will not solve"#),Leaf (P.packAddress "Would you dress in women's clothes for me? That really turns me on ;)"#),Leaf (P.packAddress "I will NOT be ignored..."#),Leaf (P.packAddress "I Think you're fake"#),Leaf (P.packAddress "Guys who can speak latin really turn me on."#),Leaf (P.packAddress "Does your mommie know you're here, little naughty boy?"#),Leaf (P.packAddress "Im going to be a movie star. I just applied online for this new movie with chris farley. It only cost me $50!"#),Leaf (P.packAddress "Have you ever killed a hobo? Ive found eating their liver gives me strength. I think i may just be short on b vitamines."#),Leaf (P.packAddress "What is your favorite cheese? Mines baloney."#),Leaf (P.packAddress "My instant messenger doesn't work."#),Leaf (P.packAddress "What do you think of Foucault's theory of binary constructs as an imprisoning limitation on power imposed by arbiters?"#),Leaf (P.packAddress "I have a boyfriend, but he likes to watch."#),Leaf (P.packAddress "If something takes a lot of effort to do, it probably ain't worth doing."#),Leaf (P.packAddress "I don't think you are the one you say you are!"#),Leaf (P.packAddress "Are you adopted by trolls?"#),Leaf (P.packAddress "I consider rabits as an endangered species. "#),Leaf (P.packAddress "Beer, it's so much more than just a breakfast drink!"#),Leaf (P.packAddress "If I was looking for anonymous casual sex, I wouldn't be sitting here behind my computer talking to you!"#),Leaf (P.packAddress "Sex is the mysticism of materialism and the only possible religion in a materialistic society."#),Leaf (P.packAddress "I have 2 c what u look like.. u have pic?? URL?? NOT a fake please.. ill know!"#),Leaf (P.packAddress "So, tell me your biggest and darkest secret. Something that no one knows of you."#),Leaf (P.packAddress "you sir are no gentleman"#),Leaf (P.packAddress "tell me a joke.. I like men that makes me laugh"#),Leaf (P.packAddress "where can I a see a picture of you?? URL??"#),Leaf (P.packAddress "Fuck me like im a school boy"#),Leaf (P.packAddress "You think this is a botiecall??"#)]), ( mkRegex (P.packAddress ".*"#),Leaf (P.packAddress "If you see this, gentle sir, know that you are being trolled by a poorly configured VixenLove program"#))]