{-# LANGUAGE OverloadedStrings #-}
module Fake.Provider.Person.EN_US
( personName
, femaleName
, maleName
, femalePrefix
, femalePrefixList
, malePrefix
, malePrefixList
, femaleSuffix
, femaleSuffixList
, maleSuffix
, maleSuffixList
, firstName
, femaleFirstName
, femaleNameList
, maleFirstName
, maleNameList
, lastName
, lastNameList
) where
import Data.Bifunctor
import Data.Text (Text)
import Fake.Combinators
import Fake.Provider.Lang
import Fake.Types
personName :: FGen Text
personName :: FGen Text
personName = [FGen Text] -> FGen Text
forall a. [FGen a] -> FGen a
oneof [FGen Text
femaleName, FGen Text
maleName]
femaleName :: FGen Text
femaleName :: FGen Text
femaleName = Phrase -> Text
phraseText (Phrase -> Text) -> FGen Phrase -> FGen Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Int, FGen Phrase)] -> FGen Phrase
forall a. [(Int, FGen a)] -> FGen a
frequency
[ (Int
5, [FGen SingleWord] -> FGen Phrase
phrase [FGen SingleWord
femaleFirstName, FGen SingleWord
lastName])
, (Int
1, [FGen SingleWord] -> FGen Phrase
phrase [FGen SingleWord
femalePrefix, FGen SingleWord
femaleFirstName, FGen SingleWord
lastName])
, (Int
1, [FGen SingleWord] -> FGen Phrase
phrase [FGen SingleWord
femaleFirstName, FGen SingleWord
lastName, FGen SingleWord
femaleSuffix])
, (Int
1, [FGen SingleWord] -> FGen Phrase
phrase [FGen SingleWord
femalePrefix, FGen SingleWord
femaleFirstName, FGen SingleWord
lastName, FGen SingleWord
femaleSuffix])
]
maleName :: FGen Text
maleName :: FGen Text
maleName = Phrase -> Text
phraseText (Phrase -> Text) -> FGen Phrase -> FGen Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Int, FGen Phrase)] -> FGen Phrase
forall a. [(Int, FGen a)] -> FGen a
frequency
[ (Int
5, [FGen SingleWord] -> FGen Phrase
phrase [FGen SingleWord
maleFirstName, FGen SingleWord
lastName])
, (Int
1, [FGen SingleWord] -> FGen Phrase
phrase [FGen SingleWord
malePrefix, FGen SingleWord
maleFirstName, FGen SingleWord
lastName])
, (Int
1, [FGen SingleWord] -> FGen Phrase
phrase [FGen SingleWord
maleFirstName, FGen SingleWord
lastName, FGen SingleWord
maleSuffix])
, (Int
1, [FGen SingleWord] -> FGen Phrase
phrase [FGen SingleWord
malePrefix, FGen SingleWord
maleFirstName, FGen SingleWord
lastName, FGen SingleWord
maleSuffix])
]
femalePrefix :: FGen SingleWord
femalePrefix :: FGen SingleWord
femalePrefix = [SingleWord] -> FGen SingleWord
forall a. [a] -> FGen a
elements [SingleWord]
femalePrefixList
femalePrefixList :: [SingleWord]
femalePrefixList :: [SingleWord]
femalePrefixList = [SingleWord
"Mrs.", SingleWord
"Ms.", SingleWord
"Miss", SingleWord
"Dr."]
malePrefix :: FGen SingleWord
malePrefix :: FGen SingleWord
malePrefix = [SingleWord] -> FGen SingleWord
forall a. [a] -> FGen a
elements [SingleWord]
malePrefixList
malePrefixList :: [SingleWord]
malePrefixList :: [SingleWord]
malePrefixList = [SingleWord
"Mr.", SingleWord
"Dr."]
femaleSuffix :: FGen SingleWord
femaleSuffix :: FGen SingleWord
femaleSuffix = [SingleWord] -> FGen SingleWord
forall a. [a] -> FGen a
elements [SingleWord]
femaleSuffixList
femaleSuffixList :: [SingleWord]
femaleSuffixList :: [SingleWord]
femaleSuffixList = [SingleWord
"MD", SingleWord
"DDS", SingleWord
"PhD", SingleWord
"DVM"]
maleSuffix :: FGen SingleWord
maleSuffix :: FGen SingleWord
maleSuffix = [SingleWord] -> FGen SingleWord
forall a. [a] -> FGen a
elements [SingleWord]
maleSuffixList
maleSuffixList :: [SingleWord]
maleSuffixList :: [SingleWord]
maleSuffixList = [SingleWord
"Jr.", SingleWord
"Sr.", SingleWord
"I", SingleWord
"II", SingleWord
"III",SingleWord
"IV", SingleWord
"V", SingleWord
"MD", SingleWord
"DDS", SingleWord
"PhD", SingleWord
"DVM"]
firstName :: FGen SingleWord
firstName :: FGen SingleWord
firstName = [FGen SingleWord] -> FGen SingleWord
forall a. [FGen a] -> FGen a
oneof [FGen SingleWord
femaleFirstName, FGen SingleWord
maleFirstName]
femaleFirstName :: FGen SingleWord
femaleFirstName :: FGen SingleWord
femaleFirstName = [(Int, FGen SingleWord)] -> FGen SingleWord
forall a. [(Int, FGen a)] -> FGen a
frequency ([(Int, FGen SingleWord)] -> FGen SingleWord)
-> [(Int, FGen SingleWord)] -> FGen SingleWord
forall a b. (a -> b) -> a -> b
$ ((Int, Text) -> (Int, FGen SingleWord))
-> [(Int, Text)] -> [(Int, FGen SingleWord)]
forall a b. (a -> b) -> [a] -> [b]
map ((Text -> FGen SingleWord) -> (Int, Text) -> (Int, FGen SingleWord)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (SingleWord -> FGen SingleWord
forall (m :: * -> *) a. Monad m => a -> m a
return (SingleWord -> FGen SingleWord)
-> (Text -> SingleWord) -> Text -> FGen SingleWord
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> SingleWord
SingleWord)) [(Int, Text)]
femaleNameList
femaleNameList :: [(Int, Text)]
femaleNameList :: [(Int, Text)]
femaleNameList = [(Int, Text)]
femaleNameList00
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
femaleNameList01
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
femaleNameList02
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
femaleNameList03
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
femaleNameList04
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
femaleNameList05
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
femaleNameList06
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
femaleNameList07
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
femaleNameList08
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
femaleNameList09
femaleNameList00 :: [(Int, Text)]
femaleNameList00 :: [(Int, Text)]
femaleNameList00 =
[ (Int
3733620,Text
"Mary")
, (Int
1568111,Text
"Patricia")
, (Int
1510283,Text
"Elizabeth")
, (Int
1463109,Text
"Jennifer")
, (Int
1446736,Text
"Linda")
, (Int
1423313,Text
"Barbara")
, (Int
1124104,Text
"Margaret")
, (Int
1108550,Text
"Susan")
, (Int
1051986,Text
"Dorothy")
, (Int
1039665,Text
"Jessica")
, (Int
1015445,Text
"Sarah")
, (Int
984086,Text
"Betty")
, (Int
984075,Text
"Nancy")
, (Int
982629,Text
"Karen")
, (Int
962363,Text
"Lisa")
, (Int
896357,Text
"Helen")
, (Int
870837,Text
"Sandra")
, (Int
837145,Text
"Ashley")
, (Int
830171,Text
"Kimberly")
, (Int
826596,Text
"Donna")
, (Int
812163,Text
"Carol")
, (Int
805087,Text
"Michelle")
, (Int
803947,Text
"Emily")
, (Int
770574,Text
"Amanda")
, (Int
747383,Text
"Laura")
, (Int
747264,Text
"Melissa")
, (Int
736141,Text
"Deborah")
, (Int
734863,Text
"Stephanie")
, (Int
732041,Text
"Rebecca")
, (Int
730475,Text
"Ruth")
, (Int
730366,Text
"Anna")
, (Int
718600,Text
"Sharon")
, (Int
703771,Text
"Cynthia")
, (Int
703687,Text
"Kathleen")
, (Int
679937,Text
"Shirley")
, (Int
677040,Text
"Amy")
, (Int
656393,Text
"Angela")
, (Int
622324,Text
"Virginia")
, (Int
609624,Text
"Catherine")
, (Int
604231,Text
"Brenda")
, (Int
600165,Text
"Katherine")
, (Int
591466,Text
"Pamela")
, (Int
580795,Text
"Nicole")
, (Int
574453,Text
"Christine")
, (Int
559306,Text
"Samantha")
, (Int
550629,Text
"Janet")
, (Int
548928,Text
"Rachel")
, (Int
548353,Text
"Carolyn")
, (Int
547697,Text
"Debra")
, (Int
534173,Text
"Emma")
, (Int
530081,Text
"Frances")
, (Int
526776,Text
"Maria")
, (Int
522137,Text
"Heather")
, (Int
514882,Text
"Diane")
, (Int
514467,Text
"Evelyn")
, (Int
503360,Text
"Julie")
, (Int
502941,Text
"Joyce")
, (Int
490835,Text
"Martha")
, (Int
475580,Text
"Joan")
, (Int
474172,Text
"Alice")
, (Int
468415,Text
"Kelly")
, (Int
468137,Text
"Christina")
, (Int
463124,Text
"Victoria")
, (Int
462322,Text
"Marie")
, (Int
460700,Text
"Lauren")
, (Int
449716,Text
"Ann")
, (Int
448187,Text
"Doris")
, (Int
447229,Text
"Judith")
, (Int
445985,Text
"Jean")
, (Int
436759,Text
"Cheryl")
, (Int
433784,Text
"Megan")
, (Int
431669,Text
"Kathryn")
, (Int
424473,Text
"Andrea")
, (Int
416950,Text
"Jacqueline")
, (Int
415303,Text
"Rose")
, (Int
409399,Text
"Julia")
, (Int
408124,Text
"Sara")
, (Int
407918,Text
"Grace")
, (Int
407310,Text
"Gloria")
, (Int
405590,Text
"Teresa")
, (Int
404080,Text
"Hannah")
, (Int
402178,Text
"Janice")
, (Int
394752,Text
"Mildred")
, (Int
390113,Text
"Olivia")
, (Int
387443,Text
"Theresa")
, (Int
377964,Text
"Judy")
, (Int
373578,Text
"Beverly")
, (Int
368888,Text
"Denise")
, (Int
366196,Text
"Marilyn")
, (Int
365524,Text
"Amber")
, (Int
362848,Text
"Danielle")
, (Int
356785,Text
"Lillian")
, (Int
356329,Text
"Madison")
, (Int
356164,Text
"Brittany")
, (Int
354817,Text
"Jane")
, (Int
352103,Text
"Diana")
, (Int
338555,Text
"Lori")
, (Int
334089,Text
"Tiffany")
, (Int
331564,Text
"Natalie")
, (Int
330711,Text
"Abigail")
]
femaleNameList01 :: [(Int, Text)]
femaleNameList01 :: [(Int, Text)]
femaleNameList01 =
[ (Int
330643,Text
"Kathy")
, (Int
330129,Text
"Kayla")
, (Int
329816,Text
"Alexis")
, (Int
329507,Text
"Tammy")
, (Int
325324,Text
"Crystal")
, (Int
317163,Text
"Phyllis")
, (Int
317018,Text
"Lois")
, (Int
316759,Text
"Bonnie")
, (Int
311126,Text
"Taylor")
, (Int
308984,Text
"Erin")
, (Int
308530,Text
"Ruby")
, (Int
307037,Text
"Charlotte")
, (Int
306682,Text
"Irene")
, (Int
304630,Text
"Anne")
, (Int
298481,Text
"Alyssa")
, (Int
294367,Text
"Sophia")
, (Int
292329,Text
"Shannon")
, (Int
288489,Text
"Peggy")
, (Int
286558,Text
"Tina")
, (Int
286469,Text
"Robin")
, (Int
285392,Text
"Dawn")
, (Int
284851,Text
"Isabella")
, (Int
284477,Text
"Allison")
, (Int
281307,Text
"Louise")
, (Int
276494,Text
"Rita")
, (Int
276134,Text
"Wanda")
, (Int
275894,Text
"Annie")
, (Int
273106,Text
"Paula")
, (Int
268512,Text
"Norma")
, (Int
264262,Text
"Jamie")
, (Int
261906,Text
"Leslie")
, (Int
261840,Text
"Connie")
, (Int
261273,Text
"Audrey")
, (Int
258283,Text
"Wendy")
, (Int
257883,Text
"Marjorie")
, (Int
256951,Text
"Josephine")
, (Int
254646,Text
"Courtney")
, (Int
253406,Text
"Cindy")
, (Int
252530,Text
"Elaine")
, (Int
252385,Text
"Eleanor")
, (Int
250991,Text
"Valerie")
, (Int
249113,Text
"Ellen")
, (Int
247958,Text
"Vanessa")
, (Int
247714,Text
"Tracy")
, (Int
246263,Text
"Florence")
, (Int
243962,Text
"Brianna")
, (Int
243507,Text
"Monica")
, (Int
238105,Text
"Jasmine")
, (Int
235367,Text
"Melanie")
, (Int
234805,Text
"Sheila")
, (Int
234638,Text
"April")
, (Int
231806,Text
"Ella")
, (Int
227572,Text
"Erica")
, (Int
226931,Text
"Sherry")
, (Int
225970,Text
"Edna")
, (Int
225823,Text
"Sylvia")
, (Int
223301,Text
"Alexandra")
, (Int
222760,Text
"Carrie")
, (Int
220793,Text
"Michele")
, (Int
220108,Text
"Alicia")
, (Int
217600,Text
"Gladys")
, (Int
217496,Text
"Katie")
, (Int
215521,Text
"Kristen")
, (Int
215372,Text
"Suzanne")
, (Int
213013,Text
"Ava")
, (Int
212131,Text
"Edith")
, (Int
210434,Text
"Esther")
, (Int
209024,Text
"Veronica")
, (Int
208576,Text
"Eva")
, (Int
207877,Text
"Joanne")
, (Int
207146,Text
"Anita")
, (Int
207100,Text
"Morgan")
, (Int
206024,Text
"Dolores")
, (Int
205655,Text
"Rhonda")
, (Int
205368,Text
"Jill")
, (Int
203890,Text
"Leah")
, (Int
203870,Text
"Geraldine")
, (Int
203103,Text
"Lorraine")
, (Int
201802,Text
"Thelma")
, (Int
201335,Text
"Clara")
, (Int
201129,Text
"Caroline")
, (Int
200378,Text
"Darlene")
, (Int
200231,Text
"Pauline")
, (Int
198192,Text
"Juanita")
, (Int
197855,Text
"Gail")
, (Int
196798,Text
"Holly")
, (Int
196397,Text
"Lucille")
, (Int
195066,Text
"Ethel")
, (Int
194814,Text
"Hazel")
, (Int
194529,Text
"Sally")
, (Int
188987,Text
"Vivian")
, (Int
187850,Text
"Dana")
, (Int
186620,Text
"Mia")
, (Int
184838,Text
"Debbie")
, (Int
184193,Text
"Chloe")
, (Int
183848,Text
"June")
, (Int
183845,Text
"Brooke")
, (Int
180439,Text
"Renee")
, (Int
179599,Text
"Eileen")
, (Int
177977,Text
"Lynn")
]
femaleNameList02 :: [(Int, Text)]
femaleNameList02 :: [(Int, Text)]
femaleNameList02 =
[ (Int
176811,Text
"Kristin")
, (Int
176703,Text
"Kim")
, (Int
175442,Text
"Jo")
, (Int
171625,Text
"Tara")
, (Int
168701,Text
"Regina")
, (Int
168113,Text
"Madeline")
, (Int
167328,Text
"Cathy")
, (Int
165623,Text
"Claire")
, (Int
164531,Text
"Roberta")
, (Int
164214,Text
"Cassandra")
, (Int
163496,Text
"Bernice")
, (Int
163184,Text
"Marion")
, (Int
162561,Text
"Laurie")
, (Int
161886,Text
"Annette")
, (Int
161684,Text
"Loretta")
, (Int
160439,Text
"Beatrice")
, (Int
160096,Text
"Stacy")
, (Int
159880,Text
"Sydney")
, (Int
159764,Text
"Kaitlyn")
, (Int
158997,Text
"Colleen")
, (Int
158333,Text
"Jeanne")
, (Int
157135,Text
"Lucy")
, (Int
156205,Text
"Chelsea")
, (Int
155104,Text
"Jeanette")
, (Int
155052,Text
"Molly")
, (Int
154910,Text
"Beth")
, (Int
153451,Text
"Lindsey")
, (Int
152956,Text
"Joann")
, (Int
151763,Text
"Haley")
, (Int
151224,Text
"Savannah")
, (Int
150771,Text
"Vicki")
, (Int
150651,Text
"Yvonne")
, (Int
150195,Text
"Rosemary")
, (Int
149161,Text
"Gina")
, (Int
148398,Text
"Hailey")
, (Int
145939,Text
"Rosa")
, (Int
145054,Text
"Stacey")
, (Int
144736,Text
"Carla")
, (Int
143381,Text
"Terri")
, (Int
143254,Text
"Amelia")
, (Int
143231,Text
"Kelsey")
, (Int
140785,Text
"Destiny")
, (Int
140698,Text
"Jenna")
, (Int
140375,Text
"Shelby")
, (Int
140184,Text
"Naomi")
, (Int
139793,Text
"Maureen")
, (Int
139162,Text
"Lydia")
, (Int
139008,Text
"Heidi")
, (Int
137535,Text
"Sue")
, (Int
137406,Text
"Arlene")
, (Int
136939,Text
"Bertha")
, (Int
133137,Text
"Sabrina")
, (Int
132940,Text
"Kristina")
, (Int
132724,Text
"Constance")
, (Int
132249,Text
"Paige")
, (Int
131633,Text
"Melinda")
, (Int
131590,Text
"Wilma")
, (Int
131323,Text
"Deanna")
, (Int
130504,Text
"Carmen")
, (Int
130304,Text
"Elsie")
, (Int
129331,Text
"Charlene")
, (Int
129298,Text
"Joy")
, (Int
129200,Text
"Jessie")
, (Int
129124,Text
"Georgia")
, (Int
129053,Text
"Stella")
, (Int
128948,Text
"Marian")
, (Int
128714,Text
"Katelyn")
, (Int
128631,Text
"Marcia")
, (Int
127916,Text
"Tamara")
, (Int
127669,Text
"Gabrielle")
, (Int
127267,Text
"Jordan")
, (Int
126853,Text
"Lindsay")
, (Int
125405,Text
"Marlene")
, (Int
124635,Text
"Alma")
, (Int
123694,Text
"Faith")
, (Int
123662,Text
"Ida")
, (Int
122641,Text
"Lily")
, (Int
121135,Text
"Willie")
, (Int
120982,Text
"Erika")
, (Int
119834,Text
"Gertrude")
, (Int
119580,Text
"Claudia")
, (Int
117853,Text
"Tonya")
, (Int
117331,Text
"Mackenzie")
, (Int
116494,Text
"Marissa")
, (Int
116295,Text
"Kaylee")
, (Int
115331,Text
"Patsy")
, (Int
114961,Text
"Vera")
, (Int
114712,Text
"Agnes")
, (Int
114228,Text
"Delores")
, (Int
113544,Text
"Tanya")
, (Int
112821,Text
"Daisy")
, (Int
112301,Text
"Priscilla")
, (Int
112063,Text
"Lillie")
, (Int
112025,Text
"Violet")
, (Int
111939,Text
"Alexa")
, (Int
111627,Text
"Gwendolyn")
, (Int
111475,Text
"Nina")
, (Int
111010,Text
"Autumn")
, (Int
109714,Text
"Caitlin")
, (Int
108383,Text
"Yolanda")
]
femaleNameList03 :: [(Int, Text)]
femaleNameList03 :: [(Int, Text)]
femaleNameList03 =
[ (Int
107842,Text
"Nora")
, (Int
107773,Text
"Angelina")
, (Int
107422,Text
"Carole")
, (Int
107359,Text
"Vickie")
, (Int
107220,Text
"Alison")
, (Int
106251,Text
"Sofia")
, (Int
106187,Text
"Miranda")
, (Int
106018,Text
"Maxine")
, (Int
105827,Text
"Zoe")
, (Int
105347,Text
"Glenda")
, (Int
104218,Text
"Brandy")
, (Int
103457,Text
"Addison")
, (Int
103029,Text
"Isabel")
, (Int
103012,Text
"Gabriella")
, (Int
102969,Text
"Bessie")
, (Int
101216,Text
"Marsha")
, (Int
100761,Text
"Mariah")
, (Int
100235,Text
"Pearl")
, (Int
100149,Text
"Kylie")
, (Int
99791,Text
"Brandi")
, (Int
99338,Text
"Margie")
, (Int
98822,Text
"Avery")
, (Int
97602,Text
"Miriam")
, (Int
97495,Text
"Katrina")
, (Int
97354,Text
"Viola")
, (Int
97344,Text
"Nellie")
, (Int
97181,Text
"Lena")
, (Int
96684,Text
"Makayla")
, (Int
96610,Text
"Jocelyn")
, (Int
96120,Text
"Billie")
, (Int
96005,Text
"Toni")
, (Int
95658,Text
"Kara")
, (Int
95602,Text
"Joanna")
, (Int
95385,Text
"Christy")
, (Int
94089,Text
"Genevieve")
, (Int
93865,Text
"Ana")
, (Int
93783,Text
"Bethany")
, (Int
93694,Text
"Sophie")
, (Int
93552,Text
"Terry")
, (Int
93356,Text
"Kay")
, (Int
93339,Text
"Penny")
, (Int
93318,Text
"Sierra")
, (Int
93039,Text
"Whitney")
, (Int
92827,Text
"Natasha")
, (Int
92751,Text
"Meghan")
, (Int
92337,Text
"Dianne")
, (Int
92244,Text
"Alexandria")
, (Int
91702,Text
"Aubrey")
, (Int
91172,Text
"Kendra")
, (Int
90986,Text
"Bailey")
, (Int
90678,Text
"Jennie")
, (Int
90608,Text
"Angel")
, (Int
90574,Text
"Mattie")
, (Int
90463,Text
"Sadie")
, (Int
89920,Text
"Briana")
, (Int
89221,Text
"Minnie")
, (Int
87872,Text
"Melody")
, (Int
87076,Text
"Myrtle")
, (Int
86807,Text
"Felicia")
, (Int
86703,Text
"Jackie")
, (Int
86480,Text
"Ariana")
, (Int
86436,Text
"Riley")
, (Int
86218,Text
"Leona")
, (Int
85884,Text
"Jenny")
, (Int
85847,Text
"Cora")
, (Int
85529,Text
"Angelica")
, (Int
85274,Text
"Brooklyn")
, (Int
84678,Text
"Maggie")
, (Int
84525,Text
"Karla")
, (Int
84225,Text
"Bridget")
, (Int
84109,Text
"Tracey")
, (Int
83795,Text
"Bobbie")
, (Int
83293,Text
"Becky")
, (Int
82983,Text
"Cecilia")
, (Int
82541,Text
"Adriana")
, (Int
82162,Text
"Misty")
, (Int
81810,Text
"Maya")
, (Int
81689,Text
"Candace")
, (Int
81611,Text
"Shelly")
, (Int
81490,Text
"Sherri")
, (Int
80978,Text
"Kristine")
, (Int
80433,Text
"Jacquelyn")
, (Int
80357,Text
"Brittney")
, (Int
80280,Text
"Hope")
, (Int
79821,Text
"Arianna")
, (Int
79530,Text
"Breanna")
, (Int
78984,Text
"Desiree")
, (Int
78809,Text
"Jillian")
, (Int
77083,Text
"Rachael")
, (Int
77071,Text
"Jodi")
, (Int
76960,Text
"Dora")
, (Int
76872,Text
"Geneva")
, (Int
76233,Text
"Sheryl")
, (Int
75864,Text
"Mae")
, (Int
75610,Text
"Monique")
, (Int
74883,Text
"Isabelle")
, (Int
74803,Text
"Velma")
, (Int
74690,Text
"Madelyn")
, (Int
74349,Text
"Lynda")
, (Int
74197,Text
"Kristi")
]
femaleNameList04 :: [(Int, Text)]
femaleNameList04 :: [(Int, Text)]
femaleNameList04 =
[ (Int
74128,Text
"Aaliyah")
, (Int
74005,Text
"Gabriela")
, (Int
73781,Text
"Jade")
, (Int
73703,Text
"Marguerite")
, (Int
73479,Text
"Casey")
, (Int
72831,Text
"Kelli")
, (Int
72576,Text
"Harriet")
, (Int
72467,Text
"Mabel")
, (Int
71940,Text
"Summer")
, (Int
71503,Text
"Krystal")
, (Int
70960,Text
"Krista")
, (Int
70880,Text
"Iris")
, (Int
70442,Text
"Antoinette")
, (Int
70041,Text
"Trinity")
, (Int
69871,Text
"Shelley")
, (Int
68992,Text
"Rebekah")
, (Int
68659,Text
"Nevaeh")
, (Int
68627,Text
"Lola")
, (Int
68202,Text
"Belinda")
, (Int
68072,Text
"Bianca")
, (Int
67896,Text
"Kristy")
, (Int
67765,Text
"Meredith")
, (Int
66468,Text
"Layla")
, (Int
65668,Text
"Eunice")
, (Int
65284,Text
"Rosie")
, (Int
65099,Text
"Sandy")
, (Int
64870,Text
"Kate")
, (Int
64789,Text
"Candice")
, (Int
64229,Text
"Hilda")
, (Int
63887,Text
"Zoey")
, (Int
63770,Text
"Cheyenne")
, (Int
63596,Text
"Janie")
, (Int
63471,Text
"Gracie")
, (Int
62925,Text
"Ramona")
, (Int
62348,Text
"Irma")
, (Int
62190,Text
"Susie")
, (Int
62019,Text
"Elena")
, (Int
61762,Text
"Ariel")
, (Int
61708,Text
"Adrienne")
, (Int
61576,Text
"Peyton")
, (Int
61452,Text
"Nichole")
, (Int
61227,Text
"Jeannette")
, (Int
61151,Text
"Rosalie")
, (Int
60806,Text
"Guadalupe")
, (Int
60667,Text
"Sonya")
, (Int
60497,Text
"Ada")
, (Int
60384,Text
"Carly")
, (Int
60238,Text
"Jada")
, (Int
60081,Text
"Sonia")
, (Int
59621,Text
"Marianne")
, (Int
59561,Text
"Faye")
, (Int
59342,Text
"Patty")
, (Int
58795,Text
"Yvette")
, (Int
58756,Text
"Robyn")
, (Int
58721,Text
"Lynne")
, (Int
58711,Text
"Hattie")
, (Int
58356,Text
"Camille")
, (Int
58167,Text
"Sheri")
, (Int
58113,Text
"Alberta")
, (Int
58042,Text
"Kennedy")
, (Int
57915,Text
"Gayle")
, (Int
56976,Text
"Verna")
, (Int
56513,Text
"Maryann")
, (Int
56212,Text
"Opal")
, (Int
56169,Text
"Marcella")
, (Int
55980,Text
"Kari")
, (Int
55936,Text
"Valeria")
, (Int
55816,Text
"Kaitlin")
, (Int
55677,Text
"Gianna")
, (Int
55607,Text
"Lee")
, (Int
55358,Text
"Angie")
, (Int
55141,Text
"Blanche")
, (Int
55080,Text
"Tabitha")
, (Int
54982,Text
"Elise")
, (Int
54904,Text
"Natalia")
, (Int
54455,Text
"Karina")
, (Int
54278,Text
"Roxanne")
, (Int
53969,Text
"Fannie")
, (Int
53954,Text
"Genesis")
, (Int
53401,Text
"Daniela")
, (Int
53211,Text
"Abby")
, (Int
53102,Text
"Lila")
, (Int
52985,Text
"Alisha")
, (Int
52891,Text
"Jody")
, (Int
52679,Text
"Kendall")
, (Int
52429,Text
"Lula")
, (Int
52224,Text
"Inez")
, (Int
52145,Text
"Mckenzie")
, (Int
51998,Text
"Dianna")
, (Int
51858,Text
"Cassidy")
, (Int
51614,Text
"Skylar")
, (Int
51567,Text
"Jan")
, (Int
51234,Text
"Beulah")
, (Int
51111,Text
"Mallory")
, (Int
50617,Text
"Myra")
, (Int
50200,Text
"Mikayla")
, (Int
50188,Text
"Caitlyn")
, (Int
50112,Text
"Traci")
, (Int
49914,Text
"Celeste")
, (Int
49890,Text
"Vicky")
]
femaleNameList05 :: [(Int, Text)]
femaleNameList05 :: [(Int, Text)]
femaleNameList05 =
[ (Int
49874,Text
"Kirsten")
, (Int
49629,Text
"Olga")
, (Int
49300,Text
"Alana")
, (Int
49272,Text
"Aimee")
, (Int
48408,Text
"Kellie")
, (Int
48395,Text
"Janelle")
, (Int
48281,Text
"Camila")
, (Int
48201,Text
"Mya")
, (Int
48029,Text
"Harper")
, (Int
47804,Text
"Bernadette")
, (Int
47770,Text
"Lacey")
, (Int
47629,Text
"Gretchen")
, (Int
47612,Text
"Flora")
, (Int
47532,Text
"Juliana")
, (Int
47512,Text
"Muriel")
, (Int
47501,Text
"Cristina")
, (Int
47408,Text
"Dominique")
, (Int
47251,Text
"Mamie")
, (Int
47193,Text
"Nadine")
, (Int
46997,Text
"Payton")
, (Int
46989,Text
"Cara")
, (Int
46898,Text
"Jaime")
, (Int
46786,Text
"Allyson")
, (Int
46771,Text
"Jordyn")
, (Int
46733,Text
"Alejandra")
, (Int
46710,Text
"Annabelle")
, (Int
46007,Text
"Erma")
, (Int
45868,Text
"Lana")
, (Int
45840,Text
"Hayley")
, (Int
45812,Text
"Michaela")
, (Int
45804,Text
"Liliana")
, (Int
45752,Text
"Jaclyn")
, (Int
45624,Text
"Kerry")
, (Int
45588,Text
"Bella")
, (Int
45535,Text
"Marisa")
, (Int
45530,Text
"Della")
, (Int
45380,Text
"Rosemarie")
, (Int
44996,Text
"Serenity")
, (Int
44978,Text
"Kiara")
, (Int
44978,Text
"Raquel")
, (Int
44956,Text
"Janis")
, (Int
44848,Text
"Shelia")
, (Int
44703,Text
"Cecelia")
, (Int
44397,Text
"Callie")
, (Int
44302,Text
"Ellie")
, (Int
43961,Text
"Latoya")
, (Int
43888,Text
"Lilly")
, (Int
43631,Text
"Kelley")
, (Int
43617,Text
"Josie")
, (Int
43355,Text
"Kylee")
, (Int
43299,Text
"Lora")
, (Int
43058,Text
"Betsy")
, (Int
43017,Text
"Shawna")
, (Int
42987,Text
"Johnnie")
, (Int
42911,Text
"Paulette")
, (Int
42885,Text
"Selena")
, (Int
42776,Text
"Rochelle")
, (Int
42475,Text
"Doreen")
, (Int
42253,Text
"Christie")
, (Int
42248,Text
"Ashlyn")
, (Int
42148,Text
"Tessa")
, (Int
42048,Text
"Penelope")
, (Int
41987,Text
"Rylee")
, (Int
41938,Text
"Patti")
, (Int
41749,Text
"Celia")
, (Int
41721,Text
"Ginger")
, (Int
41639,Text
"Eloise")
, (Int
41592,Text
"Ashlee")
, (Int
41486,Text
"Reagan")
, (Int
41435,Text
"Jasmin")
, (Int
41301,Text
"Teri")
, (Int
41285,Text
"Johanna")
, (Int
41275,Text
"Esmeralda")
, (Int
40722,Text
"Jana")
, (Int
40547,Text
"Scarlett")
, (Int
40508,Text
"Adrianna")
, (Int
39983,Text
"Mable")
, (Int
39670,Text
"Meagan")
, (Int
39550,Text
"Aurora")
, (Int
39427,Text
"Laverne")
, (Int
39313,Text
"Alexia")
, (Int
39268,Text
"Corinne")
, (Int
39227,Text
"Mercedes")
, (Int
39190,Text
"Mindy")
, (Int
39154,Text
"Mona")
, (Int
38888,Text
"Cassie")
, (Int
38788,Text
"Ernestine")
, (Int
38682,Text
"Lynette")
, (Int
38450,Text
"Leticia")
, (Int
38449,Text
"Giselle")
, (Int
38444,Text
"Elisabeth")
, (Int
38275,Text
"Darla")
, (Int
38146,Text
"Jazmin")
, (Int
37960,Text
"Estelle")
, (Int
37949,Text
"Laurel")
, (Int
37900,Text
"Shari")
, (Int
37738,Text
"Adeline")
, (Int
37628,Text
"Pat")
, (Int
37226,Text
"Tricia")
, (Int
37160,Text
"Dixie")
]
femaleNameList06 :: [(Int, Text)]
femaleNameList06 :: [(Int, Text)]
femaleNameList06 =
[ (Int
36923,Text
"Nadia")
, (Int
36912,Text
"Trisha")
, (Int
36868,Text
"Ebony")
, (Int
36839,Text
"Julianna")
, (Int
36794,Text
"Mandy")
, (Int
36614,Text
"Yesenia")
, (Int
36578,Text
"Leigh")
, (Int
36475,Text
"Stacie")
, (Int
36398,Text
"Elisa")
, (Int
36365,Text
"Henrietta")
, (Int
36096,Text
"Allie")
, (Int
36064,Text
"Nikki")
, (Int
36007,Text
"Carolina")
, (Int
35877,Text
"Makenzie")
, (Int
35873,Text
"Tami")
, (Int
35760,Text
"Kristie")
, (Int
35700,Text
"Raven")
, (Int
35405,Text
"Eliza")
, (Int
35099,Text
"Eula")
, (Int
35096,Text
"Kimberley")
, (Int
35083,Text
"Alondra")
, (Int
34933,Text
"Sonja")
, (Int
34862,Text
"Kyla")
, (Int
34813,Text
"Anastasia")
, (Int
34790,Text
"Margarita")
, (Int
34740,Text
"Alissa")
, (Int
34701,Text
"Marla")
, (Int
34640,Text
"Jayla")
, (Int
34632,Text
"Ivy")
, (Int
34504,Text
"Lorena")
, (Int
34399,Text
"Kerri")
, (Int
34344,Text
"Serena")
, (Int
34078,Text
"Stefanie")
, (Int
33850,Text
"Bonita")
, (Int
33579,Text
"Olive")
, (Int
33559,Text
"Tammie")
, (Int
33391,Text
"Cheri")
, (Int
33375,Text
"Lorene")
, (Int
33358,Text
"Alaina")
, (Int
33322,Text
"Jazmine")
, (Int
33271,Text
"Tasha")
, (Int
33061,Text
"Freda")
, (Int
33045,Text
"Winifred")
, (Int
32765,Text
"Hanna")
, (Int
32688,Text
"Aliyah")
, (Int
32681,Text
"Britney")
, (Int
32656,Text
"Lucia")
, (Int
32634,Text
"Mckenna")
, (Int
32582,Text
"Madeleine")
, (Int
32503,Text
"Leila")
, (Int
32364,Text
"Sherrie")
, (Int
32307,Text
"Piper")
, (Int
32214,Text
"Clarissa")
, (Int
32177,Text
"Justine")
, (Int
32108,Text
"Bette")
, (Int
31959,Text
"Katharine")
, (Int
31901,Text
"Delaney")
, (Int
31855,Text
"Tori")
, (Int
31767,Text
"Deloris")
, (Int
31726,Text
"Ronda")
, (Int
31721,Text
"Jeannie")
, (Int
31618,Text
"Bettie")
, (Int
31453,Text
"Jewel")
, (Int
31443,Text
"Sasha")
, (Int
31379,Text
"Ciara")
, (Int
31340,Text
"Pam")
, (Int
31318,Text
"Khloe")
, (Int
31288,Text
"Francine")
, (Int
31226,Text
"Kyra")
, (Int
30974,Text
"Melba")
, (Int
30957,Text
"Mollie")
, (Int
30932,Text
"Mariana")
, (Int
30927,Text
"Patrice")
, (Int
30702,Text
"Kira")
, (Int
30645,Text
"Marina")
, (Int
30491,Text
"Tatiana")
, (Int
30411,Text
"Diamond")
, (Int
30316,Text
"Shawn")
, (Int
30207,Text
"Sallie")
, (Int
30168,Text
"Alisa")
, (Int
30139,Text
"Tracie")
, (Int
30117,Text
"Marisol")
, (Int
30117,Text
"Mayra")
, (Int
30042,Text
"Lesley")
, (Int
30001,Text
"Therese")
, (Int
29917,Text
"Tia")
, (Int
29894,Text
"Rachelle")
, (Int
29773,Text
"Ashleigh")
, (Int
29674,Text
"Kasey")
, (Int
29626,Text
"Janine")
, (Int
29428,Text
"Chelsey")
, (Int
29387,Text
"Lucinda")
, (Int
29275,Text
"Adele")
, (Int
29267,Text
"Keri")
, (Int
29236,Text
"Reba")
, (Int
29215,Text
"Christa")
, (Int
29101,Text
"Asia")
, (Int
29050,Text
"Charity")
, (Int
29032,Text
"Trina")
, (Int
28986,Text
"Aubree")
]
femaleNameList07 :: [(Int, Text)]
femaleNameList07 :: [(Int, Text)]
femaleNameList07 =
[ (Int
28781,Text
"London")
, (Int
28758,Text
"Kassandra")
, (Int
28606,Text
"Latasha")
, (Int
28507,Text
"Nettie")
, (Int
28434,Text
"Katelynn")
, (Int
28263,Text
"Laila")
, (Int
28171,Text
"Daphne")
, (Int
28146,Text
"Rena")
, (Int
28020,Text
"Dakota")
, (Int
28008,Text
"Aria")
, (Int
27790,Text
"Myrna")
, (Int
27699,Text
"Lottie")
, (Int
27645,Text
"Essie")
, (Int
27618,Text
"Eliana")
, (Int
27575,Text
"Noelle")
, (Int
27573,Text
"Fern")
, (Int
27494,Text
"Savanna")
, (Int
27415,Text
"Shayla")
, (Int
27214,Text
"Kayleigh")
, (Int
27203,Text
"Fatima")
, (Int
27093,Text
"Aileen")
, (Int
26947,Text
"Lela")
, (Int
26924,Text
"Shana")
, (Int
26897,Text
"Debora")
, (Int
26792,Text
"Lou")
, (Int
26755,Text
"Janette")
, (Int
26688,Text
"Angeline")
, (Int
26625,Text
"Reese")
, (Int
26604,Text
"Dorothea")
, (Int
26470,Text
"Dena")
, (Int
26454,Text
"Lenora")
, (Int
26253,Text
"Ollie")
, (Int
26215,Text
"Cherie")
, (Int
26143,Text
"Dina")
, (Int
26092,Text
"Brooklynn")
, (Int
26090,Text
"Frankie")
, (Int
26043,Text
"Delilah")
, (Int
25990,Text
"Eden")
, (Int
25986,Text
"Helene")
, (Int
25979,Text
"Addie")
, (Int
25973,Text
"Jolene")
, (Int
25866,Text
"Antonia")
, (Int
25788,Text
"Cierra")
, (Int
25721,Text
"Haylee")
, (Int
25678,Text
"Estella")
, (Int
25633,Text
"Randi")
, (Int
25581,Text
"Hillary")
, (Int
25490,Text
"Shanna")
, (Int
25405,Text
"Macy")
, (Int
25331,Text
"Carissa")
, (Int
25268,Text
"Cathleen")
, (Int
25156,Text
"Brenna")
, (Int
25150,Text
"Helena")
, (Int
25092,Text
"Ora")
, (Int
25091,Text
"Leanne")
, (Int
25043,Text
"Joni")
, (Int
25027,Text
"Shauna")
, (Int
24998,Text
"Candy")
, (Int
24978,Text
"Keira")
, (Int
24938,Text
"May")
, (Int
24922,Text
"Makenna")
, (Int
24916,Text
"Delia")
, (Int
24602,Text
"Angelique")
, (Int
24598,Text
"Lea")
, (Int
24530,Text
"Karin")
, (Int
24461,Text
"Valentina")
, (Int
24440,Text
"Alyson")
, (Int
24428,Text
"Julianne")
, (Int
24319,Text
"Amaya")
, (Int
24291,Text
"Etta")
, (Int
24283,Text
"Fay")
, (Int
24282,Text
"Tania")
, (Int
24241,Text
"Lucile")
, (Int
24139,Text
"Daniella")
, (Int
24103,Text
"Gwen")
, (Int
24051,Text
"Francesca")
, (Int
23850,Text
"Sondra")
, (Int
23756,Text
"Alina")
, (Int
23718,Text
"Imogene")
, (Int
23522,Text
"Brielle")
, (Int
23495,Text
"Cameron")
, (Int
23494,Text
"Jayne")
, (Int
23367,Text
"Jodie")
, (Int
23329,Text
"Staci")
, (Int
23325,Text
"Paris")
, (Int
23155,Text
"Tiana")
, (Int
23080,Text
"Ina")
, (Int
23018,Text
"Kailey")
, (Int
22990,Text
"Lara")
, (Int
22858,Text
"Camryn")
, (Int
22855,Text
"Lorna")
, (Int
22837,Text
"Iva")
, (Int
22805,Text
"Polly")
, (Int
22712,Text
"Eugenia")
, (Int
22678,Text
"Leilani")
, (Int
22663,Text
"Athena")
, (Int
22579,Text
"Alivia")
, (Int
22538,Text
"Luz")
, (Int
22435,Text
"Goldie")
, (Int
22401,Text
"Cleo")
]
femaleNameList08 :: [(Int, Text)]
femaleNameList08 :: [(Int, Text)]
femaleNameList08 =
[ (Int
22388,Text
"Phoebe")
, (Int
22258,Text
"Clare")
, (Int
22167,Text
"Elva")
, (Int
22144,Text
"Jenifer")
, (Int
22109,Text
"Taryn")
, (Int
22045,Text
"Paisley")
, (Int
21971,Text
"Chasity")
, (Int
21959,Text
"Blanca")
, (Int
21927,Text
"Jewell")
, (Int
21886,Text
"Rosetta")
, (Int
21849,Text
"Susanne")
, (Int
21760,Text
"Trudy")
, (Int
21724,Text
"Alayna")
, (Int
21681,Text
"Kenya")
, (Int
21671,Text
"Kiana")
, (Int
21562,Text
"Lizbeth")
, (Int
21559,Text
"Talia")
, (Int
21501,Text
"Hayden")
, (Int
21498,Text
"Heaven")
, (Int
21264,Text
"Maribel")
, (Int
21263,Text
"Izabella")
, (Int
21254,Text
"Francis")
, (Int
21246,Text
"Emilia")
, (Int
21182,Text
"Julissa")
, (Int
21118,Text
"Effie")
, (Int
21100,Text
"Tiara")
, (Int
21088,Text
"Aniyah")
, (Int
21072,Text
"Tamika")
, (Int
21056,Text
"Hallie")
, (Int
20991,Text
"Logan")
, (Int
20842,Text
"Hilary")
, (Int
20806,Text
"Bettye")
, (Int
20804,Text
"Ingrid")
, (Int
20703,Text
"Juliet")
, (Int
20698,Text
"Imani")
, (Int
20694,Text
"Rosalind")
, (Int
20633,Text
"Jeannine")
, (Int
20617,Text
"Simone")
, (Int
20576,Text
"Fiona")
, (Int
20520,Text
"Glenna")
, (Int
20473,Text
"Arielle")
, (Int
20427,Text
"Leann")
, (Int
20361,Text
"Lizzie")
, (Int
20301,Text
"Ashlynn")
, (Int
20301,Text
"Ericka")
, (Int
20298,Text
"Paola")
, (Int
20240,Text
"Mila")
, (Int
20223,Text
"Lyla")
, (Int
20195,Text
"Latonya")
, (Int
20191,Text
"Maritza")
, (Int
20184,Text
"Leola")
, (Int
20092,Text
"Skyler")
, (Int
20084,Text
"Elsa")
, (Int
20068,Text
"Chris")
, (Int
20020,Text
"Bridgette")
, (Int
19982,Text
"Sienna")
, (Int
19947,Text
"Bobbi")
, (Int
19931,Text
"Jeanine")
, (Int
19928,Text
"Audra")
, (Int
19879,Text
"Elvira")
, (Int
19759,Text
"Keisha")
, (Int
19746,Text
"Luella")
, (Int
19667,Text
"Emilee")
, (Int
19620,Text
"Ola")
, (Int
19579,Text
"Hadley")
, (Int
19527,Text
"Jayden")
, (Int
19514,Text
"Sheena")
, (Int
19501,Text
"Willa")
, (Int
19473,Text
"Deana")
, (Int
19413,Text
"Ryan")
, (Int
19340,Text
"Larissa")
, (Int
19309,Text
"Kali")
, (Int
19262,Text
"Lorie")
, (Int
19171,Text
"Quinn")
, (Int
19064,Text
"Tonia")
, (Int
19026,Text
"Lexi")
, (Int
19000,Text
"Jimmie")
, (Int
18956,Text
"Jeri")
, (Int
18927,Text
"Harmony")
, (Int
18804,Text
"Harley")
, (Int
18781,Text
"Angelia")
, (Int
18761,Text
"Jami")
, (Int
18643,Text
"Robbie")
, (Int
18641,Text
"Marley")
, (Int
18484,Text
"Clarice")
, (Int
18451,Text
"Brynn")
, (Int
18428,Text
"Willow")
, (Int
18364,Text
"Margo")
, (Int
18362,Text
"Ryleigh")
, (Int
18291,Text
"Christi")
, (Int
18265,Text
"Brianne")
, (Int
18260,Text
"Carmela")
, (Int
18208,Text
"James")
, (Int
18132,Text
"Sidney")
, (Int
18126,Text
"Greta")
, (Int
18059,Text
"Aisha")
, (Int
18054,Text
"Nia")
, (Int
17990,Text
"India")
, (Int
17981,Text
"Kaylie")
, (Int
17861,Text
"Emilie")
]
femaleNameList09 :: [(Int, Text)]
femaleNameList09 :: [(Int, Text)]
femaleNameList09 =
[ (Int
17859,Text
"Leanna")
, (Int
17836,Text
"Ladonna")
, (Int
17819,Text
"Dale")
, (Int
17801,Text
"Marcy")
, (Int
17785,Text
"Juliette")
, (Int
17737,Text
"Millie")
, (Int
17674,Text
"Bernadine")
, (Int
17613,Text
"Viviana")
, (Int
17571,Text
"Ximena")
, (Int
17523,Text
"Rene")
, (Int
17492,Text
"Alta")
, (Int
17490,Text
"Malia")
, (Int
17438,Text
"Darcy")
, (Int
17418,Text
"Nell")
, (Int
17397,Text
"Kamryn")
, (Int
17364,Text
"Tabatha")
, (Int
17339,Text
"Eve")
, (Int
17328,Text
"Elaina")
, (Int
17287,Text
"Kiera")
, (Int
17282,Text
"Alexus")
, (Int
17270,Text
"Tanisha")
, (Int
17206,Text
"Michael")
, (Int
17118,Text
"Terrie")
, (Int
17090,Text
"Matilda")
, (Int
17087,Text
"Alanna")
, (Int
17081,Text
"Susana")
, (Int
17004,Text
"Gale")
, (Int
17002,Text
"Katlyn")
, (Int
16973,Text
"Karissa")
, (Int
16970,Text
"Yasmin")
, (Int
16924,Text
"Lauryn")
, (Int
16913,Text
"Evangeline")
, (Int
16903,Text
"Ashton")
, (Int
16886,Text
"Devon")
, (Int
16883,Text
"Nelda")
, (Int
16882,Text
"Amie")
, (Int
16876,Text
"Selma")
, (Int
16868,Text
"Rhoda")
, (Int
16850,Text
"Cadence")
, (Int
16777,Text
"Noemi")
, (Int
16756,Text
"Perla")
, (Int
16749,Text
"Dorthy")
, (Int
16714,Text
"Baylee")
, (Int
16685,Text
"Lupe")
, (Int
16674,Text
"Christian")
, (Int
16622,Text
"Bryanna")
, (Int
16594,Text
"Kelsie")
, (Int
16573,Text
"Madalyn")
, (Int
16458,Text
"Latisha")
, (Int
16458,Text
"Lenore")
, (Int
16361,Text
"Colette")
, (Int
16230,Text
"Presley")
, (Int
16222,Text
"Noreen")
, (Int
16220,Text
"Kiley")
, (Int
16220,Text
"Ruthie")
, (Int
16150,Text
"Jayda")
, (Int
16081,Text
"Lacy")
, (Int
16012,Text
"Tatum")
, (Int
15971,Text
"Adelaide")
, (Int
15928,Text
"Emely")
, (Int
15835,Text
"Precious")
, (Int
15809,Text
"Araceli")
, (Int
15769,Text
"Kassidy")
, (Int
15731,Text
"Esperanza")
, (Int
15709,Text
"Maddison")
, (Int
15679,Text
"John")
, (Int
15675,Text
"Melisa")
, (Int
15586,Text
"Claudette")
, (Int
15549,Text
"Rosalyn")
, (Int
15546,Text
"Kaylin")
, (Int
15546,Text
"Charlie")
, (Int
15526,Text
"Nayeli")
, (Int
15467,Text
"Silvia")
, (Int
15410,Text
"Mara")
, (Int
15341,Text
"Kyleigh")
, (Int
15267,Text
"Mikaela")
, (Int
15260,Text
"Dulce")
, (Int
15228,Text
"Elnora")
, (Int
15189,Text
"Luna")
, (Int
15132,Text
"Saundra")
, (Int
15114,Text
"Robert")
, (Int
15091,Text
"Maura")
, (Int
15077,Text
"Harriett")
, (Int
15077,Text
"Mavis")
, (Int
15013,Text
"Cortney")
, (Int
14967,Text
"Frieda")
, (Int
14935,Text
"Lorrie")
, (Int
14912,Text
"Annmarie")
, (Int
14904,Text
"Katy")
, (Int
14841,Text
"Skye")
, (Int
14767,Text
"Gay")
, (Int
14718,Text
"Beatriz")
, (Int
14684,Text
"Devin")
, (Int
14678,Text
"Elyse")
, (Int
14660,Text
"Ila")
, (Int
14644,Text
"Nola")
, (Int
14627,Text
"Carmella")
, (Int
14617,Text
"Elinor")
, (Int
14617,Text
"Chandra")
, (Int
14610,Text
"Malinda")
]
maleFirstName :: FGen SingleWord
maleFirstName :: FGen SingleWord
maleFirstName = [(Int, FGen SingleWord)] -> FGen SingleWord
forall a. [(Int, FGen a)] -> FGen a
frequency ([(Int, FGen SingleWord)] -> FGen SingleWord)
-> [(Int, FGen SingleWord)] -> FGen SingleWord
forall a b. (a -> b) -> a -> b
$ ((Int, Text) -> (Int, FGen SingleWord))
-> [(Int, Text)] -> [(Int, FGen SingleWord)]
forall a b. (a -> b) -> [a] -> [b]
map ((Text -> FGen SingleWord) -> (Int, Text) -> (Int, FGen SingleWord)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (SingleWord -> FGen SingleWord
forall (m :: * -> *) a. Monad m => a -> m a
return (SingleWord -> FGen SingleWord)
-> (Text -> SingleWord) -> Text -> FGen SingleWord
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> SingleWord
SingleWord)) [(Int, Text)]
maleNameList
maleNameList :: [(Int, Text)]
maleNameList :: [(Int, Text)]
maleNameList = [(Int, Text)]
maleNameList00
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
maleNameList01
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
maleNameList02
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
maleNameList03
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
maleNameList04
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
maleNameList05
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
maleNameList06
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
maleNameList07
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
maleNameList08
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
maleNameList09
maleNameList00 :: [(Int, Text)]
maleNameList00 :: [(Int, Text)]
maleNameList00 =
[ (Int
4954037,Text
"James")
, (Int
4840467,Text
"John")
, (Int
4716978,Text
"Robert")
, (Int
4310511,Text
"Michael")
, (Int
3845199,Text
"William")
, (Int
3566154,Text
"David")
, (Int
2532760,Text
"Richard")
, (Int
2491293,Text
"Joseph")
, (Int
2251908,Text
"Charles")
, (Int
2223640,Text
"Thomas")
, (Int
2001078,Text
"Christopher")
, (Int
1866293,Text
"Daniel")
, (Int
1561248,Text
"Matthew")
, (Int
1404066,Text
"Anthony")
, (Int
1402101,Text
"Donald")
, (Int
1357937,Text
"Paul")
, (Int
1341830,Text
"Mark")
, (Int
1322761,Text
"George")
, (Int
1273341,Text
"Steven")
, (Int
1262387,Text
"Kenneth")
, (Int
1247633,Text
"Andrew")
, (Int
1213917,Text
"Edward")
, (Int
1181368,Text
"Joshua")
, (Int
1158944,Text
"Brian")
, (Int
1157267,Text
"Kevin")
, (Int
1074521,Text
"Ronald")
, (Int
1059934,Text
"Timothy")
, (Int
1016641,Text
"Jason")
, (Int
970378,Text
"Jeffrey")
, (Int
907427,Text
"Ryan")
, (Int
896997,Text
"Gary")
, (Int
880959,Text
"Jacob")
, (Int
879024,Text
"Nicholas")
, (Int
866465,Text
"Eric")
, (Int
847268,Text
"Stephen")
, (Int
818880,Text
"Frank")
, (Int
817906,Text
"Jonathan")
, (Int
801488,Text
"Larry")
, (Int
766349,Text
"Scott")
, (Int
763019,Text
"Justin")
, (Int
746352,Text
"Raymond")
, (Int
744587,Text
"Brandon")
, (Int
703106,Text
"Samuel")
, (Int
702752,Text
"Gregory")
, (Int
691499,Text
"Benjamin")
, (Int
660152,Text
"Patrick")
, (Int
650943,Text
"Jack")
, (Int
626604,Text
"Alexander")
, (Int
611704,Text
"Dennis")
, (Int
605577,Text
"Jerry")
, (Int
589855,Text
"Henry")
, (Int
573357,Text
"Tyler")
, (Int
559365,Text
"Walter")
, (Int
557315,Text
"Peter")
, (Int
556299,Text
"Aaron")
, (Int
553409,Text
"Douglas")
, (Int
544224,Text
"Jose")
, (Int
534139,Text
"Adam")
, (Int
525297,Text
"Harold")
, (Int
521578,Text
"Zachary")
, (Int
521387,Text
"Nathan")
, (Int
477652,Text
"Carl")
, (Int
475217,Text
"Arthur")
, (Int
471737,Text
"Kyle")
, (Int
441995,Text
"Gerald")
, (Int
441316,Text
"Albert")
, (Int
439984,Text
"Lawrence")
, (Int
434800,Text
"Roger")
, (Int
431309,Text
"Keith")
, (Int
428393,Text
"Jeremy")
, (Int
422729,Text
"Joe")
, (Int
419008,Text
"Terry")
, (Int
412285,Text
"Sean")
, (Int
411515,Text
"Willie")
, (Int
396076,Text
"Christian")
, (Int
394713,Text
"Jesse")
, (Int
392088,Text
"Austin")
, (Int
389255,Text
"Ralph")
, (Int
384225,Text
"Ethan")
, (Int
379009,Text
"Billy")
, (Int
377119,Text
"Bruce")
, (Int
374623,Text
"Roy")
, (Int
372552,Text
"Bryan")
, (Int
363707,Text
"Louis")
, (Int
362319,Text
"Eugene")
, (Int
355992,Text
"Harry")
, (Int
355386,Text
"Jordan")
, (Int
347534,Text
"Wayne")
, (Int
341813,Text
"Russell")
, (Int
340961,Text
"Dylan")
, (Int
339390,Text
"Alan")
, (Int
333747,Text
"Juan")
, (Int
332586,Text
"Noah")
, (Int
329615,Text
"Philip")
, (Int
324932,Text
"Randy")
, (Int
324829,Text
"Vincent")
, (Int
323886,Text
"Howard")
, (Int
314693,Text
"Gabriel")
, (Int
309940,Text
"Bobby")
, (Int
305881,Text
"Johnny")
]
maleNameList01 :: [(Int, Text)]
maleNameList01 :: [(Int, Text)]
maleNameList01 =
[ (Int
303507,Text
"Victor")
, (Int
301431,Text
"Phillip")
, (Int
299161,Text
"Shawn")
, (Int
297953,Text
"Bradley")
, (Int
297290,Text
"Fred")
, (Int
296411,Text
"Travis")
, (Int
295413,Text
"Craig")
, (Int
291870,Text
"Martin")
, (Int
291581,Text
"Logan")
, (Int
288496,Text
"Stanley")
, (Int
282114,Text
"Jimmy")
, (Int
279104,Text
"Danny")
, (Int
278678,Text
"Todd")
, (Int
277725,Text
"Cody")
, (Int
277676,Text
"Leonard")
, (Int
275854,Text
"Carlos")
, (Int
275127,Text
"Ernest")
, (Int
273388,Text
"Dale")
, (Int
266454,Text
"Francis")
, (Int
265307,Text
"Clarence")
, (Int
263604,Text
"Earl")
, (Int
259966,Text
"Luis")
, (Int
258610,Text
"Caleb")
, (Int
257643,Text
"Alex")
, (Int
257447,Text
"Allen")
, (Int
257097,Text
"Joel")
, (Int
256618,Text
"Cameron")
, (Int
252668,Text
"Nathaniel")
, (Int
251916,Text
"Curtis")
, (Int
249155,Text
"Elijah")
, (Int
247590,Text
"Isaac")
, (Int
247266,Text
"Evan")
, (Int
245085,Text
"Frederick")
, (Int
243359,Text
"Marvin")
, (Int
243237,Text
"Tony")
, (Int
242749,Text
"Norman")
, (Int
241843,Text
"Rodney")
, (Int
240403,Text
"Glenn")
, (Int
237870,Text
"Luke")
, (Int
237314,Text
"Mason")
, (Int
237112,Text
"Chad")
, (Int
236185,Text
"Antonio")
, (Int
234456,Text
"Melvin")
, (Int
234182,Text
"Steve")
, (Int
226375,Text
"Jeffery")
, (Int
225913,Text
"Edwin")
, (Int
224920,Text
"Derek")
, (Int
221954,Text
"Alfred")
, (Int
220883,Text
"Marcus")
, (Int
217989,Text
"Ricky")
, (Int
216612,Text
"Jesus")
, (Int
214740,Text
"Lee")
, (Int
214301,Text
"Adrian")
, (Int
213426,Text
"Angel")
, (Int
213045,Text
"Theodore")
, (Int
211657,Text
"Lucas")
, (Int
211408,Text
"Hunter")
, (Int
210021,Text
"Ian")
, (Int
207966,Text
"Herbert")
, (Int
205723,Text
"Troy")
, (Int
202333,Text
"Dustin")
, (Int
201919,Text
"Jackson")
, (Int
199757,Text
"Wesley")
, (Int
198265,Text
"Eddie")
, (Int
197474,Text
"Mike")
, (Int
195732,Text
"Jared")
, (Int
193653,Text
"Randall")
, (Int
189597,Text
"Connor")
, (Int
189198,Text
"Calvin")
, (Int
188943,Text
"Isaiah")
, (Int
188586,Text
"Bernard")
, (Int
188375,Text
"Ray")
, (Int
187132,Text
"Leroy")
, (Int
184664,Text
"Shane")
, (Int
182370,Text
"Jay")
, (Int
181524,Text
"Julian")
, (Int
180537,Text
"Jayden")
, (Int
178308,Text
"Corey")
, (Int
178093,Text
"Ronnie")
, (Int
176888,Text
"Barry")
, (Int
176118,Text
"Clifford")
, (Int
175196,Text
"Oscar")
, (Int
174036,Text
"Jeremiah")
, (Int
173467,Text
"Manuel")
, (Int
171760,Text
"Leo")
, (Int
171510,Text
"Tommy")
, (Int
170893,Text
"Aiden")
, (Int
166903,Text
"Warren")
, (Int
166708,Text
"Miguel")
, (Int
166355,Text
"Dean")
, (Int
163921,Text
"Blake")
, (Int
163160,Text
"Jon")
, (Int
161585,Text
"Don")
, (Int
160391,Text
"Gavin")
, (Int
156964,Text
"Mitchell")
, (Int
155305,Text
"Brett")
, (Int
155280,Text
"Darrell")
, (Int
154457,Text
"Seth")
, (Int
154318,Text
"Jerome")
, (Int
154267,Text
"Bill")
]
maleNameList02 :: [(Int, Text)]
maleNameList02 :: [(Int, Text)]
maleNameList02 =
[ (Int
154175,Text
"Liam")
, (Int
153323,Text
"Leon")
, (Int
152576,Text
"Trevor")
, (Int
152065,Text
"Owen")
, (Int
149839,Text
"Lloyd")
, (Int
149810,Text
"Micheal")
, (Int
149429,Text
"Alvin")
, (Int
148750,Text
"Chase")
, (Int
148536,Text
"Dominic")
, (Int
147858,Text
"Erik")
, (Int
146713,Text
"Gordon")
, (Int
146469,Text
"Devin")
, (Int
140623,Text
"Jim")
, (Int
139072,Text
"Floyd")
, (Int
138681,Text
"Mario")
, (Int
138653,Text
"Derrick")
, (Int
138459,Text
"Vernon")
, (Int
138400,Text
"Charlie")
, (Int
138014,Text
"Chris")
, (Int
137026,Text
"Edgar")
, (Int
135949,Text
"Brent")
, (Int
135815,Text
"Marc")
, (Int
135668,Text
"Landon")
, (Int
135334,Text
"Max")
, (Int
134615,Text
"Lewis")
, (Int
133606,Text
"Ricardo")
, (Int
127899,Text
"Franklin")
, (Int
126791,Text
"Clyde")
, (Int
126520,Text
"Maurice")
, (Int
125995,Text
"Francisco")
, (Int
125372,Text
"Tom")
, (Int
124944,Text
"Alejandro")
, (Int
124343,Text
"Carter")
, (Int
123982,Text
"Wyatt")
, (Int
123900,Text
"Jorge")
, (Int
123658,Text
"Garrett")
, (Int
123254,Text
"Cory")
, (Int
123147,Text
"Cole")
, (Int
122180,Text
"Clayton")
, (Int
121797,Text
"Gene")
, (Int
120787,Text
"Gilbert")
, (Int
120775,Text
"Sebastian")
, (Int
119199,Text
"Glen")
, (Int
119043,Text
"Ivan")
, (Int
119012,Text
"Herman")
, (Int
118723,Text
"Xavier")
, (Int
117971,Text
"Lester")
, (Int
117061,Text
"Levi")
, (Int
117036,Text
"Colin")
, (Int
116586,Text
"Oliver")
, (Int
115959,Text
"Andre")
, (Int
114441,Text
"Jeff")
, (Int
112820,Text
"Grant")
, (Int
112307,Text
"Jake")
, (Int
110759,Text
"Duane")
, (Int
108804,Text
"Spencer")
, (Int
107864,Text
"Elmer")
, (Int
107371,Text
"Chester")
, (Int
107208,Text
"Milton")
, (Int
106254,Text
"Jimmie")
, (Int
106234,Text
"Casey")
, (Int
106155,Text
"Harvey")
, (Int
104936,Text
"Reginald")
, (Int
104426,Text
"Colton")
, (Int
104333,Text
"Ruben")
, (Int
104226,Text
"Taylor")
, (Int
103879,Text
"Leslie")
, (Int
103469,Text
"Aidan")
, (Int
103161,Text
"Bryce")
, (Int
103136,Text
"Sam")
, (Int
103122,Text
"Roberto")
, (Int
102123,Text
"Preston")
, (Int
102046,Text
"Brayden")
, (Int
100517,Text
"Tristan")
, (Int
99876,Text
"Lance")
, (Int
99304,Text
"Darren")
, (Int
98856,Text
"Jessie")
, (Int
97927,Text
"Dan")
, (Int
97554,Text
"Eduardo")
, (Int
97003,Text
"Neil")
, (Int
96663,Text
"Arnold")
, (Int
96203,Text
"Cecil")
, (Int
95698,Text
"Hector")
, (Int
95407,Text
"Diego")
, (Int
95256,Text
"Eli")
, (Int
94169,Text
"Karl")
, (Int
93108,Text
"Johnnie")
, (Int
90992,Text
"Javier")
, (Int
90632,Text
"Clinton")
, (Int
90065,Text
"Roland")
, (Int
89654,Text
"Fernando")
, (Int
88834,Text
"Allan")
, (Int
88406,Text
"Johnathan")
, (Int
88339,Text
"Carson")
, (Int
88257,Text
"Bob")
, (Int
88235,Text
"Hayden")
, (Int
88100,Text
"Darryl")
, (Int
88012,Text
"Omar")
, (Int
86969,Text
"Everett")
, (Int
86875,Text
"Parker")
]
maleNameList03 :: [(Int, Text)]
maleNameList03 :: [(Int, Text)]
maleNameList03 =
[ (Int
86766,Text
"Lonnie")
, (Int
86683,Text
"Tanner")
, (Int
85747,Text
"Brendan")
, (Int
84624,Text
"Riley")
, (Int
83597,Text
"Josiah")
, (Int
82381,Text
"Dakota")
, (Int
82321,Text
"Marshall")
, (Int
82051,Text
"Pedro")
, (Int
81636,Text
"Jamie")
, (Int
81491,Text
"Kurt")
, (Int
81314,Text
"Andy")
, (Int
80726,Text
"Micah")
, (Int
80186,Text
"Brady")
, (Int
80089,Text
"Brad")
, (Int
79796,Text
"Raul")
, (Int
78843,Text
"Guy")
, (Int
78776,Text
"Nicolas")
, (Int
78768,Text
"Maxwell")
, (Int
78464,Text
"Tim")
, (Int
78295,Text
"Nolan")
, (Int
78057,Text
"Rick")
, (Int
77472,Text
"Kelly")
, (Int
76508,Text
"Abraham")
, (Int
76461,Text
"Claude")
, (Int
75931,Text
"Andres")
, (Int
75090,Text
"Tyrone")
, (Int
74754,Text
"Greg")
, (Int
74585,Text
"Jackie")
, (Int
74494,Text
"Dalton")
, (Int
74353,Text
"Ross")
, (Int
74186,Text
"Byron")
, (Int
73721,Text
"Damian")
, (Int
73488,Text
"Sidney")
, (Int
73434,Text
"Wallace")
, (Int
73050,Text
"Dwight")
, (Int
71674,Text
"Rafael")
, (Int
71481,Text
"Dwayne")
, (Int
70875,Text
"Sergio")
, (Int
70531,Text
"Collin")
, (Int
70360,Text
"Angelo")
, (Int
69806,Text
"Ted")
, (Int
69653,Text
"Hugh")
, (Int
69396,Text
"Kaleb")
, (Int
69316,Text
"Cooper")
, (Int
69275,Text
"Drew")
, (Int
69197,Text
"Willard")
, (Int
69166,Text
"Nelson")
, (Int
68857,Text
"Ben")
, (Int
68535,Text
"Mathew")
, (Int
68464,Text
"Jaden")
, (Int
68381,Text
"Ramon")
, (Int
67859,Text
"Freddie")
, (Int
67813,Text
"Armando")
, (Int
67472,Text
"Perry")
, (Int
67254,Text
"Cesar")
, (Int
67012,Text
"Terrence")
, (Int
66553,Text
"Devon")
, (Int
66520,Text
"Shaun")
, (Int
66472,Text
"Julius")
, (Int
64933,Text
"Emmanuel")
, (Int
64753,Text
"Marco")
, (Int
64555,Text
"Miles")
, (Int
64546,Text
"Terrance")
, (Int
64520,Text
"Erick")
, (Int
63792,Text
"Kent")
, (Int
63464,Text
"Stuart")
, (Int
63382,Text
"Kirk")
, (Int
63364,Text
"Jaime")
, (Int
63259,Text
"Marion")
, (Int
62902,Text
"Virgil")
, (Int
62678,Text
"Clifton")
, (Int
62225,Text
"Wade")
, (Int
62054,Text
"Morris")
, (Int
61468,Text
"Jonathon")
, (Int
61109,Text
"Elias")
, (Int
60284,Text
"Ayden")
, (Int
59899,Text
"Ashton")
, (Int
59857,Text
"Harrison")
, (Int
59286,Text
"Dillon")
, (Int
58903,Text
"Brody")
, (Int
58792,Text
"Kristopher")
, (Int
58667,Text
"Daryl")
, (Int
58642,Text
"Alexis")
, (Int
58319,Text
"Rickey")
, (Int
58286,Text
"Felix")
, (Int
58246,Text
"Cristian")
, (Int
58206,Text
"Giovanni")
, (Int
58076,Text
"Damon")
, (Int
57289,Text
"Fredrick")
, (Int
56735,Text
"Dominick")
, (Int
56488,Text
"Tracy")
, (Int
56170,Text
"Donnie")
, (Int
55951,Text
"Dave")
, (Int
55595,Text
"Alberto")
, (Int
55360,Text
"Julio")
, (Int
55117,Text
"Lorenzo")
, (Int
54622,Text
"Malcolm")
, (Int
54539,Text
"Caden")
, (Int
54416,Text
"Jonah")
, (Int
54374,Text
"Jaxon")
]
maleNameList04 :: [(Int, Text)]
maleNameList04 :: [(Int, Text)]
maleNameList04 =
[ (Int
54310,Text
"Kaden")
, (Int
53538,Text
"Luther")
, (Int
53524,Text
"Dallas")
, (Int
53421,Text
"Gage")
, (Int
52972,Text
"Gerard")
, (Int
52501,Text
"Enrique")
, (Int
52124,Text
"Israel")
, (Int
51789,Text
"Salvatore")
, (Int
51775,Text
"Trenton")
, (Int
51742,Text
"Roman")
, (Int
51684,Text
"Leonardo")
, (Int
51551,Text
"Rex")
, (Int
51211,Text
"Damien")
, (Int
51097,Text
"Lyle")
, (Int
50981,Text
"Grayson")
, (Int
50708,Text
"Jace")
, (Int
50412,Text
"Geoffrey")
, (Int
50385,Text
"Earnest")
, (Int
50210,Text
"Hubert")
, (Int
49724,Text
"Alfredo")
, (Int
49448,Text
"Arturo")
, (Int
49447,Text
"Homer")
, (Int
49333,Text
"Donovan")
, (Int
49241,Text
"Wilbur")
, (Int
49177,Text
"Otis")
, (Int
48930,Text
"Simon")
, (Int
48791,Text
"Neal")
, (Int
48684,Text
"Dana")
, (Int
48667,Text
"Conner")
, (Int
48387,Text
"Wendell")
, (Int
48113,Text
"Shannon")
, (Int
47691,Text
"Bryson")
, (Int
47633,Text
"Joey")
, (Int
47598,Text
"Lynn")
, (Int
47441,Text
"Gerardo")
, (Int
47037,Text
"Colby")
, (Int
46715,Text
"Alec")
, (Int
46704,Text
"Trent")
, (Int
46522,Text
"Darius")
, (Int
46494,Text
"Santiago")
, (Int
46277,Text
"Kerry")
, (Int
46171,Text
"Rudolph")
, (Int
46171,Text
"Kenny")
, (Int
46167,Text
"Kelvin")
, (Int
45796,Text
"Bennie")
, (Int
45322,Text
"Leland")
, (Int
44954,Text
"Horace")
, (Int
44735,Text
"Avery")
, (Int
44631,Text
"Marcos")
, (Int
44256,Text
"Randolph")
, (Int
44203,Text
"Bryant")
, (Int
44084,Text
"Rene")
, (Int
43882,Text
"Garry")
, (Int
43543,Text
"Josue")
, (Int
43542,Text
"Carlton")
, (Int
43333,Text
"Willis")
, (Int
43087,Text
"Peyton")
, (Int
42676,Text
"Emanuel")
, (Int
42589,Text
"Nick")
, (Int
42526,Text
"Edmund")
, (Int
42439,Text
"Salvador")
, (Int
42006,Text
"Chance")
, (Int
41863,Text
"Ira")
, (Int
41839,Text
"Rudy")
, (Int
41706,Text
"Benny")
, (Int
41650,Text
"Orlando")
, (Int
41350,Text
"Delbert")
, (Int
41064,Text
"Ty")
, (Int
40973,Text
"Roderick")
, (Int
40802,Text
"Braden")
, (Int
40545,Text
"Abel")
, (Int
40308,Text
"Forrest")
, (Int
40187,Text
"Loren")
, (Int
39941,Text
"Alton")
, (Int
39940,Text
"Malik")
, (Int
39901,Text
"Robin")
, (Int
39644,Text
"Archie")
, (Int
39563,Text
"Pablo")
, (Int
39510,Text
"Hudson")
, (Int
39305,Text
"Grady")
, (Int
38809,Text
"Noel")
, (Int
38804,Text
"Myron")
, (Int
38784,Text
"Ernesto")
, (Int
38743,Text
"Jermaine")
, (Int
38361,Text
"Emmett")
, (Int
38357,Text
"Malachi")
, (Int
38328,Text
"Wilson")
, (Int
37938,Text
"Dante")
, (Int
37932,Text
"Sammy")
, (Int
37619,Text
"Tyson")
, (Int
37527,Text
"Kayden")
, (Int
37238,Text
"Zane")
, (Int
36707,Text
"Clark")
, (Int
36673,Text
"Brock")
, (Int
36580,Text
"Braxton")
, (Int
36293,Text
"Pete")
, (Int
36105,Text
"Lowell")
, (Int
35981,Text
"Frankie")
, (Int
35883,Text
"Sylvester")
, (Int
35796,Text
"Irving")
]
maleNameList05 :: [(Int, Text)]
maleNameList05 :: [(Int, Text)]
maleNameList05 =
[ (Int
35714,Text
"Skyler")
, (Int
35698,Text
"Cedric")
, (Int
35656,Text
"Morgan")
, (Int
35433,Text
"Asher")
, (Int
35426,Text
"Junior")
, (Int
34966,Text
"Wilbert")
, (Int
34952,Text
"Lincoln")
, (Int
34704,Text
"Trey")
, (Int
34521,Text
"Camden")
, (Int
34429,Text
"Jalen")
, (Int
34286,Text
"Woodrow")
, (Int
34269,Text
"Quentin")
, (Int
34248,Text
"Alfonso")
, (Int
34186,Text
"Elliott")
, (Int
33825,Text
"Nickolas")
, (Int
33634,Text
"Gustavo")
, (Int
33519,Text
"Alonzo")
, (Int
33394,Text
"Fabian")
, (Int
33392,Text
"Saul")
, (Int
33294,Text
"Ryder")
, (Int
33119,Text
"Gregg")
, (Int
32999,Text
"Easton")
, (Int
32962,Text
"Graham")
, (Int
32892,Text
"Emilio")
, (Int
32679,Text
"Roosevelt")
, (Int
32670,Text
"Ron")
, (Int
32507,Text
"Sherman")
, (Int
32489,Text
"Tucker")
, (Int
32486,Text
"Laurence")
, (Int
32342,Text
"Ellis")
, (Int
32330,Text
"Griffin")
, (Int
32086,Text
"Kim")
, (Int
32037,Text
"Ervin")
, (Int
32005,Text
"Irvin")
, (Int
31581,Text
"Myles")
, (Int
31577,Text
"Weston")
, (Int
31509,Text
"Ismael")
, (Int
31382,Text
"Mateo")
, (Int
31159,Text
"Demetrius")
, (Int
31159,Text
"Terrell")
, (Int
31084,Text
"Harley")
, (Int
31018,Text
"Sawyer")
, (Int
30929,Text
"Clay")
, (Int
30845,Text
"Elliot")
, (Int
30821,Text
"Carroll")
, (Int
30797,Text
"Bentley")
, (Int
30605,Text
"Jaxson")
, (Int
30431,Text
"Silas")
, (Int
30332,Text
"Sheldon")
, (Int
30304,Text
"Ezra")
, (Int
30232,Text
"Moses")
, (Int
29963,Text
"Jaylen")
, (Int
29855,Text
"Keegan")
, (Int
29694,Text
"Lane")
, (Int
29572,Text
"Terence")
, (Int
29564,Text
"Darin")
, (Int
29477,Text
"Jasper")
, (Int
29449,Text
"Rodolfo")
, (Int
29381,Text
"Tommie")
, (Int
29358,Text
"August")
, (Int
29330,Text
"Drake")
, (Int
29244,Text
"Mack")
, (Int
29014,Text
"Ezekiel")
, (Int
28919,Text
"Cornelius")
, (Int
28899,Text
"Dawson")
, (Int
28770,Text
"Jamal")
, (Int
28683,Text
"Orville")
, (Int
28604,Text
"Corbin")
, (Int
28602,Text
"Kendall")
, (Int
28564,Text
"Toby")
, (Int
28499,Text
"Chandler")
, (Int
28381,Text
"Lamar")
, (Int
28252,Text
"Cayden")
, (Int
28251,Text
"Beau")
, (Int
28237,Text
"Rufus")
, (Int
28195,Text
"Marty")
, (Int
28189,Text
"Ken")
, (Int
28138,Text
"Kaiden")
, (Int
27961,Text
"Jody")
, (Int
27916,Text
"Brennan")
, (Int
27868,Text
"Jayson")
, (Int
27814,Text
"Zackary")
, (Int
27791,Text
"Kai")
, (Int
27774,Text
"Desmond")
, (Int
27613,Text
"Billie")
, (Int
27598,Text
"Jakob")
, (Int
27571,Text
"Axel")
, (Int
27183,Text
"Kameron")
, (Int
27165,Text
"Jude")
, (Int
27156,Text
"Clint")
, (Int
27039,Text
"Teddy")
, (Int
27023,Text
"Zachery")
, (Int
26962,Text
"Elbert")
, (Int
26905,Text
"Dane")
, (Int
26823,Text
"Conrad")
, (Int
26806,Text
"Dewey")
, (Int
26699,Text
"Bret")
, (Int
26665,Text
"Doyle")
, (Int
26647,Text
"Darrin")
, (Int
26600,Text
"Lukas")
]
maleNameList06 :: [(Int, Text)]
maleNameList06 :: [(Int, Text)]
maleNameList06 =
[ (Int
26570,Text
"Bradford")
, (Int
26520,Text
"Guillermo")
, (Int
26493,Text
"Bennett")
, (Int
26489,Text
"Dexter")
, (Int
26294,Text
"Esteban")
, (Int
26047,Text
"Quinn")
, (Int
25949,Text
"Felipe")
, (Int
25638,Text
"Kyler")
, (Int
25566,Text
"Hugo")
, (Int
25449,Text
"Dick")
, (Int
25288,Text
"Merle")
, (Int
25281,Text
"Darrel")
, (Int
25278,Text
"Marlon")
, (Int
25277,Text
"Blaine")
, (Int
25255,Text
"Randal")
, (Int
25019,Text
"Deandre")
, (Int
24870,Text
"Heath")
, (Int
24792,Text
"Will")
, (Int
24786,Text
"Branden")
, (Int
24711,Text
"Gilberto")
, (Int
24573,Text
"Stewart")
, (Int
24512,Text
"Aubrey")
, (Int
24456,Text
"Reid")
, (Int
24363,Text
"Jaiden")
, (Int
24303,Text
"Amos")
, (Int
24292,Text
"Quinton")
, (Int
24248,Text
"Solomon")
, (Int
24158,Text
"Darnell")
, (Int
23864,Text
"Declan")
, (Int
23636,Text
"Sterling")
, (Int
23620,Text
"Maddox")
, (Int
23602,Text
"Bert")
, (Int
23496,Text
"Kendrick")
, (Int
23367,Text
"Amir")
, (Int
23345,Text
"Zachariah")
, (Int
23339,Text
"Lionel")
, (Int
23311,Text
"Cade")
, (Int
23265,Text
"Moises")
, (Int
23217,Text
"Wilfred")
, (Int
23164,Text
"Antoine")
, (Int
22975,Text
"Jarrod")
, (Int
22936,Text
"Rylan")
, (Int
22896,Text
"Emil")
, (Int
22882,Text
"Joaquin")
, (Int
22791,Text
"Adan")
, (Int
22768,Text
"Percy")
, (Int
22714,Text
"Pat")
, (Int
22659,Text
"Rocco")
, (Int
22590,Text
"Reed")
, (Int
22570,Text
"Brenden")
, (Int
22400,Text
"Tomas")
, (Int
22368,Text
"Johnathon")
, (Int
22178,Text
"Timmy")
, (Int
22168,Text
"Dewayne")
, (Int
22058,Text
"Guadalupe")
, (Int
21943,Text
"Davis")
, (Int
21924,Text
"Mickey")
, (Int
21852,Text
"Stephan")
, (Int
21713,Text
"Zion")
, (Int
21677,Text
"Rocky")
, (Int
21503,Text
"Reuben")
, (Int
21444,Text
"Jerald")
, (Int
21424,Text
"Ramiro")
, (Int
21410,Text
"Jameson")
, (Int
21403,Text
"Louie")
, (Int
21280,Text
"Rogelio")
, (Int
21261,Text
"Ali")
, (Int
21216,Text
"Freddy")
, (Int
20940,Text
"Van")
, (Int
20856,Text
"Landen")
, (Int
20835,Text
"Boyd")
, (Int
20689,Text
"Payton")
, (Int
20664,Text
"Marquis")
, (Int
20539,Text
"Rory")
, (Int
20435,Text
"Eldon")
, (Int
20292,Text
"Royce")
, (Int
20024,Text
"Rodrigo")
, (Int
19971,Text
"Xander")
, (Int
19927,Text
"Doug")
, (Int
19870,Text
"Dominique")
, (Int
19834,Text
"Cary")
, (Int
19790,Text
"Kody")
, (Int
19737,Text
"Rolando")
, (Int
19716,Text
"Greyson")
, (Int
19637,Text
"Winston")
, (Int
19496,Text
"Lamont")
, (Int
19398,Text
"Quincy")
, (Int
19342,Text
"Isiah")
, (Int
19315,Text
"Otto")
, (Int
19216,Text
"Maximus")
, (Int
19083,Text
"Garland")
, (Int
18952,Text
"Darwin")
, (Int
18902,Text
"Jayce")
, (Int
18711,Text
"Jarrett")
, (Int
18410,Text
"Vance")
, (Int
18340,Text
"Grover")
, (Int
18322,Text
"Conor")
, (Int
18313,Text
"Anderson")
, (Int
18176,Text
"Luca")
, (Int
18079,Text
"Courtney")
]
maleNameList07 :: [(Int, Text)]
maleNameList07 :: [(Int, Text)]
maleNameList07 =
[ (Int
18075,Text
"Stacy")
, (Int
18051,Text
"Cruz")
, (Int
17958,Text
"Matt")
, (Int
17953,Text
"Noe")
, (Int
17948,Text
"Edmond")
, (Int
17931,Text
"Mauricio")
, (Int
17918,Text
"Buddy")
, (Int
17852,Text
"Tristen")
, (Int
17850,Text
"Loyd")
, (Int
17730,Text
"Thaddeus")
, (Int
17680,Text
"Jean")
, (Int
17478,Text
"Nikolas")
, (Int
17392,Text
"Jan")
, (Int
17217,Text
"Sammie")
, (Int
17182,Text
"Rodger")
, (Int
17182,Text
"Monte")
, (Int
17099,Text
"Jonas")
, (Int
17085,Text
"Harlan")
, (Int
17060,Text
"Bailey")
, (Int
16940,Text
"Robbie")
, (Int
16920,Text
"Holden")
, (Int
16797,Text
"Emiliano")
, (Int
16789,Text
"Kingston")
, (Int
16784,Text
"Keaton")
, (Int
16748,Text
"Cleveland")
, (Int
16709,Text
"Reynaldo")
, (Int
16675,Text
"Walker")
, (Int
16623,Text
"Brendon")
, (Int
16533,Text
"Issac")
, (Int
16480,Text
"Norbert")
, (Int
16474,Text
"Gael")
, (Int
16402,Text
"Zander")
, (Int
16268,Text
"Brooks")
, (Int
16246,Text
"Jess")
, (Int
16141,Text
"Aden")
, (Int
16045,Text
"Dorian")
, (Int
16032,Text
"Anton")
, (Int
15979,Text
"Nathanael")
, (Int
15936,Text
"Burton")
, (Int
15873,Text
"Murray")
, (Int
15837,Text
"Johnie")
, (Int
15632,Text
"Vicente")
, (Int
15474,Text
"Elwood")
, (Int
15446,Text
"Marlin")
, (Int
15446,Text
"Ed")
, (Int
15424,Text
"Derick")
, (Int
15376,Text
"Kristian")
, (Int
15337,Text
"Leonel")
, (Int
15267,Text
"Elton")
, (Int
15228,Text
"Phil")
, (Int
15218,Text
"Denis")
, (Int
15172,Text
"Stefan")
, (Int
15153,Text
"Jase")
, (Int
15096,Text
"Scotty")
, (Int
15049,Text
"Ryker")
, (Int
15042,Text
"Bobbie")
, (Int
15011,Text
"Zackery")
, (Int
14995,Text
"Brantley")
, (Int
14986,Text
"Ignacio")
, (Int
14973,Text
"Efrain")
, (Int
14917,Text
"Jefferson")
, (Int
14771,Text
"Skylar")
, (Int
14737,Text
"Erwin")
, (Int
14716,Text
"Emerson")
, (Int
14688,Text
"Caiden")
, (Int
14649,Text
"Elvin")
, (Int
14617,Text
"Chuck")
, (Int
14434,Text
"Roscoe")
, (Int
14255,Text
"Rusty")
, (Int
14241,Text
"Javon")
, (Int
14182,Text
"Kurtis")
, (Int
14166,Text
"Ariel")
, (Int
14165,Text
"Kobe")
, (Int
14130,Text
"Khalil")
, (Int
14117,Text
"Justice")
, (Int
14116,Text
"Ahmad")
, (Int
14073,Text
"King")
, (Int
13804,Text
"Humberto")
, (Int
13797,Text
"Dion")
, (Int
13625,Text
"Vaughn")
, (Int
13509,Text
"Carmen")
, (Int
13491,Text
"Damion")
, (Int
13470,Text
"Duncan")
, (Int
13430,Text
"Judah")
, (Int
13365,Text
"Cash")
, (Int
13356,Text
"Santos")
, (Int
13340,Text
"Rashad")
, (Int
13335,Text
"Uriel")
, (Int
13313,Text
"Tate")
, (Int
13273,Text
"Romeo")
, (Int
13217,Text
"Aron")
, (Int
13200,Text
"Keenan")
, (Int
13194,Text
"Rickie")
, (Int
13168,Text
"Amari")
, (Int
13138,Text
"Milo")
, (Int
13131,Text
"Jamar")
, (Int
13093,Text
"Raphael")
, (Int
13074,Text
"Reece")
, (Int
13039,Text
"Braylon")
, (Int
13033,Text
"Titus")
]
maleNameList08 :: [(Int, Text)]
maleNameList08 :: [(Int, Text)]
maleNameList08 =
[ (Int
13026,Text
"Kade")
, (Int
12991,Text
"Rowan")
, (Int
12982,Text
"Jarvis")
, (Int
12972,Text
"Waylon")
, (Int
12906,Text
"Cyrus")
, (Int
12874,Text
"Finn")
, (Int
12861,Text
"Donte")
, (Int
12824,Text
"Adolfo")
, (Int
12764,Text
"Bart")
, (Int
12752,Text
"Jamison")
, (Int
12732,Text
"Deshawn")
, (Int
12722,Text
"Pierre")
, (Int
12710,Text
"Tobias")
, (Int
12676,Text
"Tyrell")
, (Int
12667,Text
"Charley")
, (Int
12650,Text
"Kareem")
, (Int
12647,Text
"Curt")
, (Int
12503,Text
"Brayan")
, (Int
12408,Text
"Elvis")
, (Int
12372,Text
"Adolph")
, (Int
12359,Text
"Kermit")
, (Int
12297,Text
"Thurman")
, (Int
12288,Text
"Aldo")
, (Int
12258,Text
"Darian")
, (Int
12256,Text
"Ulysses")
, (Int
12250,Text
"Carey")
, (Int
12214,Text
"Marcel")
, (Int
12180,Text
"Kellen")
, (Int
12152,Text
"Gunner")
, (Int
12147,Text
"Alvaro")
, (Int
12066,Text
"Colten")
, (Int
12026,Text
"Mohamed")
, (Int
11943,Text
"Trevon")
, (Int
11932,Text
"Zayden")
, (Int
11914,Text
"Ned")
, (Int
11869,Text
"Hal")
, (Int
11793,Text
"Paxton")
, (Int
11787,Text
"Ernie")
, (Int
11726,Text
"Jeffry")
, (Int
11705,Text
"Agustin")
, (Int
11656,Text
"Vito")
, (Int
11646,Text
"Camron")
, (Int
11625,Text
"Al")
, (Int
11601,Text
"Osvaldo")
, (Int
11586,Text
"Bruno")
, (Int
11559,Text
"Millard")
, (Int
11542,Text
"Norris")
, (Int
11523,Text
"Braeden")
, (Int
11520,Text
"Colt")
, (Int
11475,Text
"Irwin")
, (Int
11436,Text
"Coy")
, (Int
11397,Text
"Shelby")
, (Int
11351,Text
"Nehemiah")
, (Int
11336,Text
"Ashley")
, (Int
11316,Text
"Maximilian")
, (Int
11251,Text
"Braydon")
, (Int
11206,Text
"Josh")
, (Int
11191,Text
"Seymour")
, (Int
11153,Text
"Alphonso")
, (Int
11072,Text
"River")
, (Int
11057,Text
"Reese")
, (Int
11038,Text
"Kory")
, (Int
11030,Text
"Deon")
, (Int
10994,Text
"Rhett")
, (Int
10980,Text
"Maverick")
, (Int
10970,Text
"Demarcus")
, (Int
10951,Text
"Gus")
, (Int
10944,Text
"Barrett")
, (Int
10888,Text
"Armand")
, (Int
10878,Text
"Jordon")
, (Int
10860,Text
"Barney")
, (Int
10859,Text
"Odell")
, (Int
10858,Text
"Scot")
, (Int
10842,Text
"Moshe")
, (Int
10801,Text
"Jarred")
, (Int
10789,Text
"Donnell")
, (Int
10786,Text
"Wiley")
, (Int
10776,Text
"Monty")
, (Int
10772,Text
"Mohammad")
, (Int
10769,Text
"Bryon")
, (Int
10752,Text
"Domingo")
, (Int
10749,Text
"Kris")
, (Int
10744,Text
"Devan")
, (Int
10696,Text
"Russel")
, (Int
10689,Text
"Emory")
, (Int
10637,Text
"Galen")
, (Int
10630,Text
"Sonny")
, (Int
10619,Text
"Ahmed")
, (Int
10585,Text
"Denny")
, (Int
10571,Text
"Pierce")
, (Int
10564,Text
"Isaias")
, (Int
10539,Text
"Benito")
, (Int
10538,Text
"Coleman")
, (Int
10530,Text
"Stacey")
, (Int
10505,Text
"Brenton")
, (Int
10498,Text
"Davon")
, (Int
10485,Text
"Carmine")
, (Int
10481,Text
"Tyree")
, (Int
10454,Text
"Quintin")
, (Int
10446,Text
"Carlo")
]
maleNameList09 :: [(Int, Text)]
maleNameList09 :: [(Int, Text)]
maleNameList09 =
[ (Int
10405,Text
"Ezequiel")
, (Int
10396,Text
"Ronny")
, (Int
10379,Text
"Maynard")
, (Int
10370,Text
"Abram")
, (Int
10350,Text
"Laverne")
, (Int
10336,Text
"Chadwick")
, (Int
10319,Text
"Gerry")
, (Int
10281,Text
"Wilmer")
, (Int
10193,Text
"Sanford")
, (Int
10129,Text
"Phoenix")
, (Int
10124,Text
"Merlin")
, (Int
10122,Text
"Emery")
, (Int
10108,Text
"Houston")
, (Int
10099,Text
"Brice")
, (Int
10088,Text
"Maximiliano")
, (Int
10062,Text
"Ollie")
, (Int
10047,Text
"Monroe")
, (Int
10032,Text
"Gunnar")
, (Int
10024,Text
"Antwan")
, (Int
9973,Text
"Jax")
, (Int
9962,Text
"Mohammed")
, (Int
9939,Text
"Prince")
, (Int
9916,Text
"Markus")
, (Int
9896,Text
"Ari")
, (Int
9886,Text
"Jett")
, (Int
9861,Text
"Joesph")
, (Int
9828,Text
"Porter")
, (Int
9813,Text
"Kolton")
, (Int
9735,Text
"Davion")
, (Int
9669,Text
"Linwood")
, (Int
9666,Text
"Orion")
, (Int
9634,Text
"Mary")
, (Int
9590,Text
"Denver")
, (Int
9518,Text
"Cohen")
, (Int
9492,Text
"Delmar")
, (Int
9458,Text
"Stevie")
, (Int
9452,Text
"Garret")
, (Int
9426,Text
"Tevin")
, (Int
9412,Text
"Devonte")
, (Int
9382,Text
"Cullen")
, (Int
9352,Text
"Weldon")
, (Int
9343,Text
"Triston")
, (Int
9296,Text
"Karter")
, (Int
9294,Text
"Jarod")
, (Int
9293,Text
"Beckett")
, (Int
9281,Text
"Jamari")
, (Int
9276,Text
"Karson")
, (Int
9237,Text
"Blair")
, (Int
9202,Text
"Truman")
, (Int
9191,Text
"Gale")
, (Int
9184,Text
"Harris")
, (Int
9155,Text
"Morton")
, (Int
9093,Text
"Donny")
, (Int
9075,Text
"Kieran")
, (Int
9034,Text
"Yahir")
, (Int
9034,Text
"Matteo")
, (Int
9031,Text
"Nasir")
, (Int
8965,Text
"Frederic")
, (Int
8932,Text
"Deangelo")
, (Int
8909,Text
"Dayton")
, (Int
8899,Text
"Hollis")
, (Int
8898,Text
"Muhammad")
, (Int
8886,Text
"Major")
, (Int
8873,Text
"Clair")
, (Int
8800,Text
"Rigoberto")
, (Int
8754,Text
"Asa")
, (Int
8727,Text
"Izaiah")
, (Int
8711,Text
"Kirby")
, (Int
8700,Text
"Ward")
, (Int
8693,Text
"Hans")
, (Int
8692,Text
"Nigel")
, (Int
8671,Text
"Jaquan")
, (Int
8666,Text
"Jamel")
, (Int
8643,Text
"Gideon")
, (Int
8636,Text
"Augustus")
, (Int
8562,Text
"Kasey")
, (Int
8521,Text
"Iker")
, (Int
8472,Text
"Mekhi")
, (Int
8417,Text
"Gino")
, (Int
8395,Text
"Trace")
, (Int
8347,Text
"Ibrahim")
, (Int
8328,Text
"Forest")
, (Int
8304,Text
"Eddy")
, (Int
8304,Text
"Ulises")
, (Int
8285,Text
"Jaylin")
, (Int
8285,Text
"Brycen")
, (Int
8261,Text
"Kane")
, (Int
8251,Text
"Jaron")
, (Int
8247,Text
"Fidel")
, (Int
8236,Text
"Pasquale")
, (Int
8192,Text
"Kolby")
, (Int
8191,Text
"Octavio")
, (Int
8181,Text
"Marquise")
, (Int
8156,Text
"Clement")
, (Int
8105,Text
"Augustine")
, (Int
8089,Text
"Buford")
, (Int
8079,Text
"Korey")
, (Int
8025,Text
"Addison")
, (Int
7999,Text
"Remington")
, (Int
7980,Text
"Wilfredo")
]
lastName :: FGen SingleWord
lastName :: FGen SingleWord
lastName = [(Int, FGen SingleWord)] -> FGen SingleWord
forall a. [(Int, FGen a)] -> FGen a
frequency ([(Int, FGen SingleWord)] -> FGen SingleWord)
-> [(Int, FGen SingleWord)] -> FGen SingleWord
forall a b. (a -> b) -> a -> b
$ ((Int, Text) -> (Int, FGen SingleWord))
-> [(Int, Text)] -> [(Int, FGen SingleWord)]
forall a b. (a -> b) -> [a] -> [b]
map ((Text -> FGen SingleWord) -> (Int, Text) -> (Int, FGen SingleWord)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (SingleWord -> FGen SingleWord
forall (m :: * -> *) a. Monad m => a -> m a
return (SingleWord -> FGen SingleWord)
-> (Text -> SingleWord) -> Text -> FGen SingleWord
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> SingleWord
SingleWord)) [(Int, Text)]
lastNameList
lastNameList :: [(Int, Text)]
lastNameList :: [(Int, Text)]
lastNameList = [(Int, Text)]
lastNameList00
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
lastNameList01
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
lastNameList02
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
lastNameList03
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
lastNameList04
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
lastNameList05
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
lastNameList06
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
lastNameList07
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
lastNameList08
[(Int, Text)] -> [(Int, Text)] -> [(Int, Text)]
forall a. [a] -> [a] -> [a]
++ [(Int, Text)]
lastNameList09
lastNameList00 :: [(Int, Text)]
lastNameList00 :: [(Int, Text)]
lastNameList00 =
[ (Int
2376206,Text
"Smith")
, (Int
1857160,Text
"Johnson")
, (Int
1534042,Text
"Williams")
, (Int
1380145,Text
"Brown")
, (Int
1362755,Text
"Jones")
, (Int
1127803,Text
"Miller")
, (Int
1072335,Text
"Davis")
, (Int
858289,Text
"Garcia")
, (Int
804240,Text
"Rodriguez")
, (Int
783051,Text
"Wilson")
, (Int
775072,Text
"Martinez")
, (Int
762394,Text
"Anderson")
, (Int
720370,Text
"Taylor")
, (Int
710696,Text
"Thomas")
, (Int
706372,Text
"Hernandez")
, (Int
698671,Text
"Moore")
, (Int
672711,Text
"Martin")
, (Int
666125,Text
"Jackson")
, (Int
644368,Text
"Thompson")
, (Int
639515,Text
"White")
, (Int
621536,Text
"Lopez")
, (Int
605860,Text
"Lee")
, (Int
597718,Text
"Gonzalez")
, (Int
593542,Text
"Harris")
, (Int
548369,Text
"Clark")
, (Int
509930,Text
"Lewis")
, (Int
503028,Text
"Robinson")
, (Int
501307,Text
"Walker")
, (Int
488521,Text
"Perez")
, (Int
473568,Text
"Hall")
, (Int
465948,Text
"Young")
, (Int
463368,Text
"Allen")
, (Int
441242,Text
"Sanchez")
, (Int
440367,Text
"Wright")
, (Int
438986,Text
"King")
, (Int
420091,Text
"Scott")
, (Int
413477,Text
"Green")
, (Int
413351,Text
"Baker")
, (Int
413086,Text
"Adams")
, (Int
412236,Text
"Nelson")
, (Int
411770,Text
"Hill")
, (Int
388987,Text
"Ramirez")
, (Int
371953,Text
"Campbell")
, (Int
367433,Text
"Mitchell")
, (Int
366215,Text
"Roberts")
, (Int
362548,Text
"Carter")
, (Int
351848,Text
"Phillips")
, (Int
342237,Text
"Evans")
, (Int
335663,Text
"Turner")
, (Int
325169,Text
"Torres")
, (Int
324246,Text
"Parker")
, (Int
317848,Text
"Collins")
, (Int
317070,Text
"Edwards")
, (Int
312899,Text
"Stewart")
, (Int
312615,Text
"Flores")
, (Int
311754,Text
"Morris")
, (Int
310125,Text
"Nguyen")
, (Int
300501,Text
"Murphy")
, (Int
299463,Text
"Rivera")
, (Int
294795,Text
"Cook")
, (Int
294403,Text
"Rogers")
, (Int
276400,Text
"Morgan")
, (Int
275041,Text
"Peterson")
, (Int
270097,Text
"Cooper")
, (Int
267443,Text
"Reed")
, (Int
265916,Text
"Bailey")
, (Int
264752,Text
"Bell")
, (Int
263590,Text
"Gomez")
, (Int
260385,Text
"Kelly")
, (Int
254779,Text
"Howard")
, (Int
254121,Text
"Ward")
, (Int
253771,Text
"Cox")
, (Int
251772,Text
"Diaz")
, (Int
249533,Text
"Richardson")
, (Int
247299,Text
"Wood")
, (Int
242432,Text
"Watson")
, (Int
240751,Text
"Brooks")
, (Int
239055,Text
"Bennett")
, (Int
236713,Text
"Gray")
, (Int
233224,Text
"James")
, (Int
232511,Text
"Reyes")
, (Int
231065,Text
"Cruz")
, (Int
229390,Text
"Hughes")
, (Int
228756,Text
"Price")
, (Int
224824,Text
"Myers")
, (Int
223494,Text
"Long")
, (Int
221040,Text
"Foster")
, (Int
220902,Text
"Sanders")
, (Int
219961,Text
"Ross")
, (Int
217642,Text
"Morales")
, (Int
216553,Text
"Powell")
, (Int
215640,Text
"Sullivan")
, (Int
215432,Text
"Russell")
, (Int
214683,Text
"Ortiz")
, (Int
213737,Text
"Jenkins")
, (Int
212905,Text
"Gutierrez")
, (Int
212644,Text
"Perry")
, (Int
210879,Text
"Butler")
, (Int
210426,Text
"Barnes")
, (Int
210279,Text
"Fisher")
]
lastNameList01 :: [(Int, Text)]
lastNameList01 :: [(Int, Text)]
lastNameList01 =
[ (Int
210094,Text
"Henderson")
, (Int
208624,Text
"Coleman")
, (Int
201650,Text
"Simmons")
, (Int
198557,Text
"Patterson")
, (Int
197212,Text
"Jordan")
, (Int
195598,Text
"Reynolds")
, (Int
194331,Text
"Hamilton")
, (Int
194074,Text
"Graham")
, (Int
194067,Text
"Kim")
, (Int
193934,Text
"Gonzales")
, (Int
193443,Text
"Alexander")
, (Int
193096,Text
"Ramos")
, (Int
190760,Text
"Wallace")
, (Int
190636,Text
"Griffin")
, (Int
188464,Text
"West")
, (Int
187793,Text
"Cole")
, (Int
187473,Text
"Hayes")
, (Int
185865,Text
"Chavez")
, (Int
184420,Text
"Gibson")
, (Int
183761,Text
"Bryant")
, (Int
181934,Text
"Ellis")
, (Int
181417,Text
"Stevens")
, (Int
178414,Text
"Murray")
, (Int
178397,Text
"Ford")
, (Int
177213,Text
"Marshall")
, (Int
176334,Text
"Owens")
, (Int
176094,Text
"Mcdonald")
, (Int
175577,Text
"Harrison")
, (Int
175429,Text
"Ruiz")
, (Int
171636,Text
"Kennedy")
, (Int
170635,Text
"Wells")
, (Int
168817,Text
"Alvarez")
, (Int
168814,Text
"Woods")
, (Int
168567,Text
"Mendoza")
, (Int
165473,Text
"Castillo")
, (Int
163502,Text
"Olson")
, (Int
163481,Text
"Webb")
, (Int
163036,Text
"Washington")
, (Int
162933,Text
"Tucker")
, (Int
162686,Text
"Freeman")
, (Int
162153,Text
"Burns")
, (Int
161392,Text
"Henry")
, (Int
159989,Text
"Vasquez")
, (Int
159363,Text
"Snyder")
, (Int
158241,Text
"Simpson")
, (Int
158121,Text
"Crawford")
, (Int
157475,Text
"Jimenez")
, (Int
156848,Text
"Porter")
, (Int
155484,Text
"Mason")
, (Int
155172,Text
"Shaw")
, (Int
154934,Text
"Gordon")
, (Int
154516,Text
"Wagner")
, (Int
154410,Text
"Hunter")
, (Int
153772,Text
"Romero")
, (Int
153618,Text
"Hicks")
, (Int
152015,Text
"Dixon")
, (Int
151986,Text
"Hunt")
, (Int
150407,Text
"Palmer")
, (Int
150299,Text
"Robertson")
, (Int
150186,Text
"Black")
, (Int
150166,Text
"Holmes")
, (Int
149802,Text
"Stone")
, (Int
149664,Text
"Meyer")
, (Int
149476,Text
"Boyd")
, (Int
147909,Text
"Mills")
, (Int
147906,Text
"Warren")
, (Int
147357,Text
"Fox")
, (Int
146924,Text
"Rose")
, (Int
146440,Text
"Rice")
, (Int
146088,Text
"Moreno")
, (Int
145565,Text
"Schmidt")
, (Int
145066,Text
"Patel")
, (Int
142256,Text
"Ferguson")
, (Int
141936,Text
"Nichols")
, (Int
140786,Text
"Herrera")
, (Int
139353,Text
"Medina")
, (Int
139335,Text
"Ryan")
, (Int
139302,Text
"Fernandez")
, (Int
138811,Text
"Weaver")
, (Int
138776,Text
"Daniels")
, (Int
138742,Text
"Stephens")
, (Int
138660,Text
"Gardner")
, (Int
138028,Text
"Payne")
, (Int
137555,Text
"Kelley")
, (Int
136955,Text
"Dunn")
, (Int
136517,Text
"Pierce")
, (Int
136315,Text
"Arnold")
, (Int
136095,Text
"Tran")
, (Int
134443,Text
"Spencer")
, (Int
134231,Text
"Peters")
, (Int
134066,Text
"Hawkins")
, (Int
134034,Text
"Grant")
, (Int
133474,Text
"Hansen")
, (Int
133254,Text
"Castro")
, (Int
132645,Text
"Hoffman")
, (Int
132466,Text
"Hart")
, (Int
132457,Text
"Elliott")
, (Int
131896,Text
"Cunningham")
, (Int
131860,Text
"Knight")
, (Int
131289,Text
"Bradley")
]
lastNameList02 :: [(Int, Text)]
lastNameList02 :: [(Int, Text)]
lastNameList02 =
[ (Int
131020,Text
"Carroll")
, (Int
130793,Text
"Hudson")
, (Int
130419,Text
"Duncan")
, (Int
129982,Text
"Armstrong")
, (Int
129405,Text
"Berry")
, (Int
129320,Text
"Andrews")
, (Int
128935,Text
"Johnston")
, (Int
128794,Text
"Ray")
, (Int
128727,Text
"Lane")
, (Int
127960,Text
"Riley")
, (Int
127073,Text
"Carpenter")
, (Int
126951,Text
"Perkins")
, (Int
126399,Text
"Aguilar")
, (Int
126164,Text
"Silva")
, (Int
125653,Text
"Richards")
, (Int
125627,Text
"Willis")
, (Int
124839,Text
"Matthews")
, (Int
124614,Text
"Chapman")
, (Int
124321,Text
"Lawrence")
, (Int
124130,Text
"Garza")
, (Int
123952,Text
"Vargas")
, (Int
122447,Text
"Watkins")
, (Int
121684,Text
"Wheeler")
, (Int
121064,Text
"Larson")
, (Int
120124,Text
"Carlson")
, (Int
119868,Text
"Harper")
, (Int
119778,Text
"George")
, (Int
119604,Text
"Greene")
, (Int
119175,Text
"Burke")
, (Int
118390,Text
"Guzman")
, (Int
117939,Text
"Morrison")
, (Int
117774,Text
"Munoz")
, (Int
115540,Text
"Jacobs")
, (Int
115385,Text
"Obrien")
, (Int
115186,Text
"Lawson")
, (Int
114859,Text
"Franklin")
, (Int
114448,Text
"Lynch")
, (Int
114034,Text
"Bishop")
, (Int
113892,Text
"Carr")
, (Int
113468,Text
"Salazar")
, (Int
113160,Text
"Austin")
, (Int
112736,Text
"Mendez")
, (Int
112406,Text
"Gilbert")
, (Int
112332,Text
"Jensen")
, (Int
112216,Text
"Williamson")
, (Int
112144,Text
"Montgomery")
, (Int
112136,Text
"Harvey")
, (Int
111641,Text
"Oliver")
, (Int
109634,Text
"Howell")
, (Int
109230,Text
"Dean")
, (Int
109079,Text
"Hanson")
, (Int
107866,Text
"Weber")
, (Int
107777,Text
"Garrett")
, (Int
107244,Text
"Sims")
, (Int
107158,Text
"Burton")
, (Int
106682,Text
"Fuller")
, (Int
106631,Text
"Soto")
, (Int
106481,Text
"Mccoy")
, (Int
105804,Text
"Welch")
, (Int
105544,Text
"Chen")
, (Int
104962,Text
"Schultz")
, (Int
104281,Text
"Walters")
, (Int
104007,Text
"Reid")
, (Int
103242,Text
"Fields")
, (Int
103216,Text
"Walsh")
, (Int
102718,Text
"Little")
, (Int
102620,Text
"Fowler")
, (Int
102239,Text
"Bowman")
, (Int
102044,Text
"Davidson")
, (Int
101726,Text
"May")
, (Int
101676,Text
"Day")
, (Int
100553,Text
"Schneider")
, (Int
100491,Text
"Newman")
, (Int
100465,Text
"Brewer")
, (Int
100417,Text
"Lucas")
, (Int
99885,Text
"Holland")
, (Int
99392,Text
"Wong")
, (Int
99294,Text
"Banks")
, (Int
98993,Text
"Santos")
, (Int
98958,Text
"Curtis")
, (Int
98728,Text
"Pearson")
, (Int
98675,Text
"Delgado")
, (Int
98610,Text
"Valdez")
, (Int
98345,Text
"Pena")
, (Int
96569,Text
"Rios")
, (Int
96425,Text
"Douglas")
, (Int
96303,Text
"Sandoval")
, (Int
95896,Text
"Barrett")
, (Int
94603,Text
"Hopkins")
, (Int
94300,Text
"Keller")
, (Int
94152,Text
"Guerrero")
, (Int
93817,Text
"Stanley")
, (Int
93743,Text
"Bates")
, (Int
93723,Text
"Alvarado")
, (Int
93161,Text
"Beck")
, (Int
93131,Text
"Ortega")
, (Int
92834,Text
"Wade")
, (Int
92831,Text
"Estrada")
, (Int
92660,Text
"Contreras")
, (Int
92287,Text
"Barnett")
]
lastNameList03 :: [(Int, Text)]
lastNameList03 :: [(Int, Text)]
lastNameList03 =
[ (Int
91338,Text
"Caldwell")
, (Int
90967,Text
"Santiago")
, (Int
90618,Text
"Lambert")
, (Int
90401,Text
"Powers")
, (Int
90325,Text
"Chambers")
, (Int
90208,Text
"Nunez")
, (Int
89591,Text
"Craig")
, (Int
89198,Text
"Leonard")
, (Int
89178,Text
"Lowe")
, (Int
88917,Text
"Rhodes")
, (Int
88811,Text
"Byrd")
, (Int
88810,Text
"Gregory")
, (Int
88326,Text
"Shelton")
, (Int
88325,Text
"Frazier")
, (Int
88114,Text
"Becker")
, (Int
88016,Text
"Maldonado")
, (Int
87949,Text
"Fleming")
, (Int
87728,Text
"Vega")
, (Int
87373,Text
"Sutton")
, (Int
87226,Text
"Cohen")
, (Int
87038,Text
"Jennings")
, (Int
86346,Text
"Parks")
, (Int
86317,Text
"Mcdaniel")
, (Int
86228,Text
"Watts")
, (Int
85221,Text
"Barker")
, (Int
85212,Text
"Norris")
, (Int
85037,Text
"Vaughn")
, (Int
84926,Text
"Vazquez")
, (Int
84710,Text
"Holt")
, (Int
84699,Text
"Schwartz")
, (Int
84353,Text
"Steele")
, (Int
84233,Text
"Benson")
, (Int
83849,Text
"Neal")
, (Int
83731,Text
"Dominguez")
, (Int
83523,Text
"Horton")
, (Int
83437,Text
"Terry")
, (Int
83112,Text
"Wolfe")
, (Int
82955,Text
"Hale")
, (Int
82258,Text
"Lyons")
, (Int
82179,Text
"Graves")
, (Int
82037,Text
"Haynes")
, (Int
81933,Text
"Miles")
, (Int
81890,Text
"Park")
, (Int
81824,Text
"Warner")
, (Int
81805,Text
"Padilla")
, (Int
81524,Text
"Bush")
, (Int
81191,Text
"Thornton")
, (Int
81035,Text
"Mccarthy")
, (Int
81022,Text
"Mann")
, (Int
80944,Text
"Zimmerman")
, (Int
80936,Text
"Erickson")
, (Int
80932,Text
"Fletcher")
, (Int
80616,Text
"Mckinney")
, (Int
80493,Text
"Page")
, (Int
80190,Text
"Dawson")
, (Int
80030,Text
"Joseph")
, (Int
79951,Text
"Marquez")
, (Int
79817,Text
"Reeves")
, (Int
79685,Text
"Klein")
, (Int
79322,Text
"Espinoza")
, (Int
79151,Text
"Baldwin")
, (Int
78546,Text
"Moran")
, (Int
78323,Text
"Love")
, (Int
78141,Text
"Robbins")
, (Int
78107,Text
"Higgins")
, (Int
77561,Text
"Ball")
, (Int
77492,Text
"Cortez")
, (Int
77453,Text
"Le")
, (Int
77429,Text
"Griffith")
, (Int
77078,Text
"Bowen")
, (Int
76868,Text
"Sharp")
, (Int
76707,Text
"Cummings")
, (Int
76625,Text
"Ramsey")
, (Int
76608,Text
"Hardy")
, (Int
76539,Text
"Swanson")
, (Int
76504,Text
"Barber")
, (Int
76477,Text
"Acosta")
, (Int
76127,Text
"Luna")
, (Int
76114,Text
"Chandler")
, (Int
75135,Text
"Blair")
, (Int
75135,Text
"Daniel")
, (Int
75134,Text
"Cross")
, (Int
74839,Text
"Simon")
, (Int
74784,Text
"Dennis")
, (Int
74756,Text
"Oconnor")
, (Int
74531,Text
"Quinn")
, (Int
74285,Text
"Gross")
, (Int
73970,Text
"Navarro")
, (Int
73750,Text
"Moss")
, (Int
73522,Text
"Fitzgerald")
, (Int
73518,Text
"Doyle")
, (Int
73128,Text
"Mclaughlin")
, (Int
73071,Text
"Rojas")
, (Int
73021,Text
"Rodgers")
, (Int
72892,Text
"Stevenson")
, (Int
72642,Text
"Singh")
, (Int
72627,Text
"Yang")
, (Int
72533,Text
"Figueroa")
, (Int
72414,Text
"Harmon")
, (Int
72328,Text
"Newton")
]
lastNameList04 :: [(Int, Text)]
lastNameList04 :: [(Int, Text)]
lastNameList04 =
[ (Int
72248,Text
"Paul")
, (Int
72069,Text
"Manning")
, (Int
72052,Text
"Garner")
, (Int
71925,Text
"Mcgee")
, (Int
71754,Text
"Reese")
, (Int
71723,Text
"Francis")
, (Int
71604,Text
"Burgess")
, (Int
71528,Text
"Adkins")
, (Int
71482,Text
"Goodman")
, (Int
71344,Text
"Curry")
, (Int
71175,Text
"Brady")
, (Int
71144,Text
"Christensen")
, (Int
71103,Text
"Potter")
, (Int
70997,Text
"Walton")
, (Int
70333,Text
"Goodwin")
, (Int
70286,Text
"Mullins")
, (Int
70211,Text
"Molina")
, (Int
70123,Text
"Webster")
, (Int
70095,Text
"Fischer")
, (Int
69950,Text
"Campos")
, (Int
69843,Text
"Avila")
, (Int
69840,Text
"Sherman")
, (Int
69810,Text
"Todd")
, (Int
69756,Text
"Chang")
, (Int
69279,Text
"Blake")
, (Int
69257,Text
"Malone")
, (Int
68905,Text
"Wolf")
, (Int
68868,Text
"Hodges")
, (Int
68785,Text
"Juarez")
, (Int
68699,Text
"Gill")
, (Int
68309,Text
"Farmer")
, (Int
68145,Text
"Hines")
, (Int
68075,Text
"Gallagher")
, (Int
68046,Text
"Duran")
, (Int
68021,Text
"Hubbard")
, (Int
67923,Text
"Cannon")
, (Int
67646,Text
"Miranda")
, (Int
67570,Text
"Wang")
, (Int
67210,Text
"Saunders")
, (Int
67208,Text
"Tate")
, (Int
67154,Text
"Mack")
, (Int
67063,Text
"Hammond")
, (Int
67054,Text
"Carrillo")
, (Int
66853,Text
"Townsend")
, (Int
66738,Text
"Wise")
, (Int
66665,Text
"Ingram")
, (Int
66622,Text
"Barton")
, (Int
66534,Text
"Mejia")
, (Int
66515,Text
"Ayala")
, (Int
66412,Text
"Schroeder")
, (Int
66378,Text
"Hampton")
, (Int
66205,Text
"Rowe")
, (Int
66203,Text
"Parsons")
, (Int
65918,Text
"Frank")
, (Int
65817,Text
"Waters")
, (Int
65814,Text
"Strickland")
, (Int
65802,Text
"Osborne")
, (Int
65779,Text
"Maxwell")
, (Int
65719,Text
"Chan")
, (Int
65598,Text
"Deleon")
, (Int
65269,Text
"Norman")
, (Int
65131,Text
"Harrington")
, (Int
64815,Text
"Casey")
, (Int
64772,Text
"Patton")
, (Int
64576,Text
"Logan")
, (Int
64496,Text
"Bowers")
, (Int
64305,Text
"Mueller")
, (Int
64180,Text
"Glover")
, (Int
64141,Text
"Floyd")
, (Int
63827,Text
"Hartman")
, (Int
63825,Text
"Buchanan")
, (Int
63739,Text
"Cobb")
, (Int
63149,Text
"French")
, (Int
63023,Text
"Kramer")
, (Int
62663,Text
"Mccormick")
, (Int
62546,Text
"Clarke")
, (Int
62534,Text
"Tyler")
, (Int
62514,Text
"Gibbs")
, (Int
62344,Text
"Moody")
, (Int
62335,Text
"Conner")
, (Int
62234,Text
"Sparks")
, (Int
62116,Text
"Mcguire")
, (Int
62034,Text
"Leon")
, (Int
61979,Text
"Bauer")
, (Int
61805,Text
"Norton")
, (Int
61750,Text
"Pope")
, (Int
61747,Text
"Flynn")
, (Int
61651,Text
"Hogan")
, (Int
61619,Text
"Robles")
, (Int
61582,Text
"Salinas")
, (Int
61400,Text
"Yates")
, (Int
61199,Text
"Lindsey")
, (Int
61154,Text
"Lloyd")
, (Int
60999,Text
"Marsh")
, (Int
60874,Text
"Mcbride")
, (Int
60461,Text
"Owen")
, (Int
60045,Text
"Solis")
, (Int
59949,Text
"Pham")
, (Int
59843,Text
"Lang")
, (Int
59801,Text
"Pratt")
]
lastNameList05 :: [(Int, Text)]
lastNameList05 :: [(Int, Text)]
lastNameList05 =
[ (Int
59731,Text
"Lara")
, (Int
59682,Text
"Brock")
, (Int
59660,Text
"Ballard")
, (Int
59609,Text
"Trujillo")
, (Int
59227,Text
"Shaffer")
, (Int
59055,Text
"Drake")
, (Int
59020,Text
"Roman")
, (Int
58918,Text
"Aguirre")
, (Int
58788,Text
"Morton")
, (Int
58687,Text
"Stokes")
, (Int
58555,Text
"Lamb")
, (Int
58534,Text
"Pacheco")
, (Int
58257,Text
"Patrick")
, (Int
58233,Text
"Cochran")
, (Int
57935,Text
"Shepherd")
, (Int
57873,Text
"Cain")
, (Int
57859,Text
"Burnett")
, (Int
57822,Text
"Hess")
, (Int
57786,Text
"Li")
, (Int
57685,Text
"Cervantes")
, (Int
57357,Text
"Olsen")
, (Int
57297,Text
"Briggs")
, (Int
57210,Text
"Ochoa")
, (Int
57171,Text
"Cabrera")
, (Int
57163,Text
"Velasquez")
, (Int
57075,Text
"Montoya")
, (Int
57030,Text
"Roth")
, (Int
56744,Text
"Meyers")
, (Int
56618,Text
"Cardenas")
, (Int
56441,Text
"Fuentes")
, (Int
56153,Text
"Weiss")
, (Int
56068,Text
"Hoover")
, (Int
56068,Text
"Wilkins")
, (Int
55986,Text
"Nicholson")
, (Int
55973,Text
"Underwood")
, (Int
55903,Text
"Short")
, (Int
55821,Text
"Carson")
, (Int
55664,Text
"Morrow")
, (Int
55512,Text
"Colon")
, (Int
55466,Text
"Holloway")
, (Int
55391,Text
"Summers")
, (Int
55269,Text
"Bryan")
, (Int
55185,Text
"Petersen")
, (Int
55084,Text
"Mckenzie")
, (Int
55057,Text
"Serrano")
, (Int
54987,Text
"Wilcox")
, (Int
54924,Text
"Carey")
, (Int
54875,Text
"Clayton")
, (Int
54706,Text
"Poole")
, (Int
54691,Text
"Calderon")
, (Int
54672,Text
"Gallegos")
, (Int
54611,Text
"Greer")
, (Int
54588,Text
"Rivas")
, (Int
54575,Text
"Guerra")
, (Int
54450,Text
"Decker")
, (Int
54414,Text
"Collier")
, (Int
54401,Text
"Wall")
, (Int
54343,Text
"Whitaker")
, (Int
54296,Text
"Bass")
, (Int
54277,Text
"Flowers")
, (Int
54206,Text
"Davenport")
, (Int
54194,Text
"Conley")
, (Int
54026,Text
"Houston")
, (Int
53892,Text
"Huff")
, (Int
53771,Text
"Copeland")
, (Int
53737,Text
"Hood")
, (Int
53475,Text
"Monroe")
, (Int
53459,Text
"Massey")
, (Int
53198,Text
"Roberson")
, (Int
53180,Text
"Combs")
, (Int
53161,Text
"Franco")
, (Int
52963,Text
"Larsen")
, (Int
52689,Text
"Pittman")
, (Int
52495,Text
"Randall")
, (Int
52490,Text
"Skinner")
, (Int
52483,Text
"Wilkinson")
, (Int
52473,Text
"Kirby")
, (Int
52439,Text
"Cameron")
, (Int
52260,Text
"Bridges")
, (Int
52146,Text
"Anthony")
, (Int
52138,Text
"Richard")
, (Int
52056,Text
"Kirk")
, (Int
52004,Text
"Bruce")
, (Int
51797,Text
"Singleton")
, (Int
51796,Text
"Mathis")
, (Int
51726,Text
"Bradford")
, (Int
51679,Text
"Boone")
, (Int
51620,Text
"Abbott")
, (Int
51518,Text
"Charles")
, (Int
51504,Text
"Allison")
, (Int
51500,Text
"Sweeney")
, (Int
51489,Text
"Atkinson")
, (Int
51380,Text
"Horn")
, (Int
51361,Text
"Jefferson")
, (Int
51336,Text
"Rosales")
, (Int
51334,Text
"York")
, (Int
51177,Text
"Christian")
, (Int
51154,Text
"Phelps")
, (Int
51095,Text
"Farrell")
, (Int
51089,Text
"Castaneda")
]
lastNameList06 :: [(Int, Text)]
lastNameList06 :: [(Int, Text)]
lastNameList06 =
[ (Int
51021,Text
"Nash")
, (Int
51017,Text
"Dickerson")
, (Int
50980,Text
"Bond")
, (Int
50874,Text
"Wyatt")
, (Int
50852,Text
"Foley")
, (Int
50777,Text
"Chase")
, (Int
50748,Text
"Gates")
, (Int
50628,Text
"Vincent")
, (Int
50608,Text
"Mathews")
, (Int
50577,Text
"Hodge")
, (Int
50482,Text
"Garrison")
, (Int
50454,Text
"Trevino")
, (Int
50351,Text
"Villarreal")
, (Int
50307,Text
"Heath")
, (Int
50166,Text
"Dalton")
, (Int
50026,Text
"Valencia")
, (Int
49925,Text
"Callahan")
, (Int
49858,Text
"Hensley")
, (Int
49754,Text
"Atkins")
, (Int
49737,Text
"Huffman")
, (Int
49725,Text
"Roy")
, (Int
49601,Text
"Boyer")
, (Int
49556,Text
"Shields")
, (Int
49360,Text
"Lin")
, (Int
49330,Text
"Hancock")
, (Int
49245,Text
"Grimes")
, (Int
49241,Text
"Glenn")
, (Int
49167,Text
"Cline")
, (Int
49158,Text
"Delacruz")
, (Int
49000,Text
"Camacho")
, (Int
48833,Text
"Dillon")
, (Int
48823,Text
"Parrish")
, (Int
48656,Text
"Oneill")
, (Int
48594,Text
"Melton")
, (Int
48580,Text
"Booth")
, (Int
48527,Text
"Kane")
, (Int
48480,Text
"Berg")
, (Int
48471,Text
"Harrell")
, (Int
48462,Text
"Pitts")
, (Int
48367,Text
"Savage")
, (Int
48355,Text
"Wiggins")
, (Int
48296,Text
"Brennan")
, (Int
48282,Text
"Salas")
, (Int
48281,Text
"Marks")
, (Int
48126,Text
"Russo")
, (Int
47979,Text
"Sawyer")
, (Int
47857,Text
"Baxter")
, (Int
47839,Text
"Golden")
, (Int
47809,Text
"Hutchinson")
, (Int
47665,Text
"Liu")
, (Int
47615,Text
"Walter")
, (Int
47526,Text
"Mcdowell")
, (Int
47503,Text
"Wiley")
, (Int
47477,Text
"Rich")
, (Int
47470,Text
"Humphrey")
, (Int
47289,Text
"Johns")
, (Int
47286,Text
"Koch")
, (Int
47235,Text
"Suarez")
, (Int
47220,Text
"Hobbs")
, (Int
47128,Text
"Beard")
, (Int
47050,Text
"Gilmore")
, (Int
46895,Text
"Ibarra")
, (Int
46747,Text
"Keith")
, (Int
46739,Text
"Macias")
, (Int
46713,Text
"Khan")
, (Int
46702,Text
"Andrade")
, (Int
46682,Text
"Ware")
, (Int
46662,Text
"Stephenson")
, (Int
46609,Text
"Henson")
, (Int
46605,Text
"Wilkerson")
, (Int
46574,Text
"Dyer")
, (Int
46505,Text
"Mcclure")
, (Int
46495,Text
"Blackwell")
, (Int
46437,Text
"Mercado")
, (Int
46412,Text
"Tanner")
, (Int
46403,Text
"Eaton")
, (Int
46264,Text
"Clay")
, (Int
46196,Text
"Barron")
, (Int
46179,Text
"Beasley")
, (Int
46161,Text
"Oneal")
, (Int
45850,Text
"Preston")
, (Int
45850,Text
"Small")
, (Int
45815,Text
"Wu")
, (Int
45806,Text
"Zamora")
, (Int
45782,Text
"Macdonald")
, (Int
45763,Text
"Vance")
, (Int
45689,Text
"Snow")
, (Int
45560,Text
"Mcclain")
, (Int
45349,Text
"Stafford")
, (Int
45289,Text
"Orozco")
, (Int
45044,Text
"Barry")
, (Int
45032,Text
"English")
, (Int
44902,Text
"Shannon")
, (Int
44900,Text
"Kline")
, (Int
44874,Text
"Jacobson")
, (Int
44830,Text
"Woodard")
, (Int
44715,Text
"Huang")
, (Int
44701,Text
"Kemp")
, (Int
44698,Text
"Mosley")
, (Int
44640,Text
"Prince")
]
lastNameList07 :: [(Int, Text)]
lastNameList07 :: [(Int, Text)]
lastNameList07 =
[ (Int
44626,Text
"Merritt")
, (Int
44587,Text
"Hurst")
, (Int
44570,Text
"Villanueva")
, (Int
44454,Text
"Roach")
, (Int
44421,Text
"Nolan")
, (Int
44385,Text
"Lam")
, (Int
44245,Text
"Yoder")
, (Int
44123,Text
"Mccullough")
, (Int
43919,Text
"Lester")
, (Int
43875,Text
"Santana")
, (Int
43770,Text
"Valenzuela")
, (Int
43762,Text
"Winters")
, (Int
43720,Text
"Barrera")
, (Int
43666,Text
"Leach")
, (Int
43666,Text
"Orr")
, (Int
43556,Text
"Berger")
, (Int
43555,Text
"Mckee")
, (Int
43430,Text
"Strong")
, (Int
43395,Text
"Conway")
, (Int
43331,Text
"Stein")
, (Int
43310,Text
"Whitehead")
, (Int
43021,Text
"Bullock")
, (Int
42955,Text
"Escobar")
, (Int
42937,Text
"Knox")
, (Int
42884,Text
"Meadows")
, (Int
42839,Text
"Solomon")
, (Int
42820,Text
"Velez")
, (Int
42802,Text
"Odonnell")
, (Int
42758,Text
"Kerr")
, (Int
42669,Text
"Stout")
, (Int
42663,Text
"Blankenship")
, (Int
42642,Text
"Browning")
, (Int
42597,Text
"Kent")
, (Int
42567,Text
"Lozano")
, (Int
42512,Text
"Bartlett")
, (Int
42463,Text
"Pruitt")
, (Int
42441,Text
"Buck")
, (Int
42432,Text
"Barr")
, (Int
42369,Text
"Gaines")
, (Int
42365,Text
"Durham")
, (Int
42357,Text
"Gentry")
, (Int
42335,Text
"Mcintyre")
, (Int
42281,Text
"Sloan")
, (Int
42139,Text
"Melendez")
, (Int
42139,Text
"Rocha")
, (Int
42091,Text
"Herman")
, (Int
42080,Text
"Sexton")
, (Int
42062,Text
"Moon")
, (Int
41879,Text
"Hendricks")
, (Int
41868,Text
"Rangel")
, (Int
41863,Text
"Stark")
, (Int
41670,Text
"Lowery")
, (Int
41664,Text
"Hardin")
, (Int
41656,Text
"Hull")
, (Int
41561,Text
"Sellers")
, (Int
41459,Text
"Ellison")
, (Int
41452,Text
"Calhoun")
, (Int
41393,Text
"Gillespie")
, (Int
41348,Text
"Mora")
, (Int
41267,Text
"Knapp")
, (Int
41231,Text
"Mccall")
, (Int
41112,Text
"Morse")
, (Int
41104,Text
"Dorsey")
, (Int
41053,Text
"Weeks")
, (Int
41007,Text
"Nielsen")
, (Int
40964,Text
"Livingston")
, (Int
40923,Text
"Leblanc")
, (Int
40871,Text
"Mclean")
, (Int
40794,Text
"Bradshaw")
, (Int
40724,Text
"Glass")
, (Int
40708,Text
"Middleton")
, (Int
40706,Text
"Buckley")
, (Int
40663,Text
"Schaefer")
, (Int
40582,Text
"Frost")
, (Int
40555,Text
"Howe")
, (Int
40477,Text
"House")
, (Int
40453,Text
"Mcintosh")
, (Int
40413,Text
"Ho")
, (Int
40339,Text
"Pennington")
, (Int
40310,Text
"Reilly")
, (Int
40283,Text
"Hebert")
, (Int
40244,Text
"Mcfarland")
, (Int
40224,Text
"Hickman")
, (Int
40217,Text
"Noble")
, (Int
40203,Text
"Spears")
, (Int
40102,Text
"Conrad")
, (Int
40086,Text
"Arias")
, (Int
40046,Text
"Galvan")
, (Int
40030,Text
"Velazquez")
, (Int
40011,Text
"Huynh")
, (Int
39909,Text
"Frederick")
, (Int
39742,Text
"Randolph")
, (Int
39601,Text
"Cantu")
, (Int
39501,Text
"Fitzpatrick")
, (Int
39440,Text
"Mahoney")
, (Int
39432,Text
"Peck")
, (Int
39402,Text
"Villa")
, (Int
39369,Text
"Michael")
, (Int
39270,Text
"Donovan")
, (Int
39203,Text
"Mcconnell")
]
lastNameList08 :: [(Int, Text)]
lastNameList08 :: [(Int, Text)]
lastNameList08 =
[ (Int
39166,Text
"Walls")
, (Int
39141,Text
"Boyle")
, (Int
39111,Text
"Mayer")
, (Int
39057,Text
"Zuniga")
, (Int
39002,Text
"Giles")
, (Int
38999,Text
"Pineda")
, (Int
38975,Text
"Pace")
, (Int
38971,Text
"Hurley")
, (Int
38914,Text
"Mays")
, (Int
38896,Text
"Mcmillan")
, (Int
38844,Text
"Crosby")
, (Int
38836,Text
"Ayers")
, (Int
38759,Text
"Case")
, (Int
38714,Text
"Bentley")
, (Int
38705,Text
"Shepard")
, (Int
38702,Text
"Everett")
, (Int
38691,Text
"Pugh")
, (Int
38659,Text
"David")
, (Int
38557,Text
"Mcmahon")
, (Int
38516,Text
"Dunlap")
, (Int
38464,Text
"Bender")
, (Int
38354,Text
"Hahn")
, (Int
38340,Text
"Harding")
, (Int
38232,Text
"Acevedo")
, (Int
38158,Text
"Raymond")
, (Int
38137,Text
"Blackburn")
, (Int
37962,Text
"Duffy")
, (Int
37961,Text
"Landry")
, (Int
37903,Text
"Dougherty")
, (Int
37847,Text
"Bautista")
, (Int
37833,Text
"Shah")
, (Int
37687,Text
"Potts")
, (Int
37678,Text
"Arroyo")
, (Int
37669,Text
"Valentine")
, (Int
37662,Text
"Meza")
, (Int
37660,Text
"Gould")
, (Int
37591,Text
"Vaughan")
, (Int
37542,Text
"Fry")
, (Int
37470,Text
"Rush")
, (Int
37440,Text
"Avery")
, (Int
37353,Text
"Herring")
, (Int
37298,Text
"Dodson")
, (Int
37237,Text
"Clements")
, (Int
37234,Text
"Sampson")
, (Int
37201,Text
"Tapia")
, (Int
37145,Text
"Bean")
, (Int
37125,Text
"Lynn")
, (Int
37123,Text
"Crane")
, (Int
37116,Text
"Farley")
, (Int
37050,Text
"Cisneros")
, (Int
37032,Text
"Benton")
, (Int
37021,Text
"Ashley")
, (Int
36948,Text
"Mckay")
, (Int
36874,Text
"Finley")
, (Int
36862,Text
"Best")
, (Int
36841,Text
"Blevins")
, (Int
36833,Text
"Friedman")
, (Int
36814,Text
"Moses")
, (Int
36813,Text
"Sosa")
, (Int
36764,Text
"Blanchard")
, (Int
36729,Text
"Huber")
, (Int
36716,Text
"Frye")
, (Int
36694,Text
"Krueger")
, (Int
36546,Text
"Bernard")
, (Int
36539,Text
"Rosario")
, (Int
36531,Text
"Rubio")
, (Int
36442,Text
"Mullen")
, (Int
36439,Text
"Benjamin")
, (Int
36433,Text
"Haley")
, (Int
36422,Text
"Chung")
, (Int
36421,Text
"Moyer")
, (Int
36390,Text
"Choi")
, (Int
36288,Text
"Horne")
, (Int
36285,Text
"Yu")
, (Int
36242,Text
"Woodward")
, (Int
36079,Text
"Ali")
, (Int
36037,Text
"Nixon")
, (Int
36024,Text
"Hayden")
, (Int
35980,Text
"Rivers")
, (Int
35839,Text
"Estes")
, (Int
35718,Text
"Mccarty")
, (Int
35715,Text
"Richmond")
, (Int
35701,Text
"Stuart")
, (Int
35648,Text
"Maynard")
, (Int
35616,Text
"Brandt")
, (Int
35610,Text
"Oconnell")
, (Int
35599,Text
"Hanna")
, (Int
35565,Text
"Sanford")
, (Int
35554,Text
"Sheppard")
, (Int
35539,Text
"Church")
, (Int
35521,Text
"Burch")
, (Int
35464,Text
"Levy")
, (Int
35453,Text
"Rasmussen")
, (Int
35442,Text
"Coffey")
, (Int
35400,Text
"Ponce")
, (Int
35389,Text
"Faulkner")
, (Int
35387,Text
"Donaldson")
, (Int
35326,Text
"Schmitt")
, (Int
35282,Text
"Novak")
, (Int
35227,Text
"Costa")
]
lastNameList09 :: [(Int, Text)]
lastNameList09 :: [(Int, Text)]
lastNameList09 =
[ (Int
35196,Text
"Montes")
, (Int
35101,Text
"Booker")
, (Int
35074,Text
"Cordova")
, (Int
35001,Text
"Waller")
, (Int
34999,Text
"Arellano")
, (Int
34970,Text
"Maddox")
, (Int
34888,Text
"Mata")
, (Int
34824,Text
"Bonilla")
, (Int
34812,Text
"Stanton")
, (Int
34788,Text
"Compton")
, (Int
34786,Text
"Kaufman")
, (Int
34770,Text
"Dudley")
, (Int
34763,Text
"Mcpherson")
, (Int
34736,Text
"Beltran")
, (Int
34698,Text
"Dickson")
, (Int
34692,Text
"Mccann")
, (Int
34684,Text
"Villegas")
, (Int
34682,Text
"Proctor")
, (Int
34675,Text
"Hester")
, (Int
34674,Text
"Cantrell")
, (Int
34650,Text
"Daugherty")
, (Int
34615,Text
"Cherry")
, (Int
34575,Text
"Bray")
, (Int
34541,Text
"Davila")
, (Int
34498,Text
"Rowland")
, (Int
34472,Text
"Levine")
, (Int
34472,Text
"Madden")
, (Int
34435,Text
"Spence")
, (Int
34430,Text
"Good")
, (Int
34374,Text
"Irwin")
, (Int
34352,Text
"Werner")
, (Int
34345,Text
"Krause")
, (Int
34278,Text
"Petty")
, (Int
34251,Text
"Whitney")
, (Int
34233,Text
"Baird")
, (Int
34084,Text
"Hooper")
, (Int
34079,Text
"Pollard")
, (Int
34068,Text
"Zavala")
, (Int
34050,Text
"Jarvis")
, (Int
34041,Text
"Holden")
, (Int
34032,Text
"Haas")
, (Int
34032,Text
"Hendrix")
, (Int
34031,Text
"Mcgrath")
, (Int
33962,Text
"Bird")
, (Int
33922,Text
"Lucero")
, (Int
33914,Text
"Terrell")
, (Int
33868,Text
"Riggs")
, (Int
33843,Text
"Joyce")
, (Int
33797,Text
"Mercer")
, (Int
33797,Text
"Rollins")
, (Int
33773,Text
"Galloway")
, (Int
33745,Text
"Duke")
, (Int
33717,Text
"Odom")
, (Int
33508,Text
"Andersen")
, (Int
33494,Text
"Downs")
, (Int
33464,Text
"Hatfield")
, (Int
33441,Text
"Benitez")
, (Int
33411,Text
"Archer")
, (Int
33348,Text
"Huerta")
, (Int
33339,Text
"Travis")
, (Int
33239,Text
"Mcneil")
, (Int
33209,Text
"Hinton")
, (Int
33202,Text
"Zhang")
, (Int
33194,Text
"Hays")
, (Int
33126,Text
"Mayo")
, (Int
33068,Text
"Fritz")
, (Int
33040,Text
"Branch")
, (Int
32953,Text
"Mooney")
, (Int
32925,Text
"Ewing")
, (Int
32864,Text
"Ritter")
, (Int
32772,Text
"Esparza")
, (Int
32735,Text
"Frey")
, (Int
32676,Text
"Braun")
, (Int
32672,Text
"Gay")
, (Int
32654,Text
"Riddle")
, (Int
32644,Text
"Haney")
, (Int
32567,Text
"Kaiser")
, (Int
32466,Text
"Holder")
, (Int
32433,Text
"Chaney")
, (Int
32386,Text
"Mcknight")
, (Int
32377,Text
"Gamble")
, (Int
32333,Text
"Vang")
, (Int
32287,Text
"Cooley")
, (Int
32282,Text
"Carney")
, (Int
32242,Text
"Cowan")
, (Int
32228,Text
"Forbes")
, (Int
32174,Text
"Ferrell")
, (Int
32165,Text
"Davies")
, (Int
32147,Text
"Barajas")
, (Int
32069,Text
"Shea")
, (Int
32044,Text
"Osborn")
, (Int
32042,Text
"Bright")
, (Int
32015,Text
"Cuevas")
, (Int
31995,Text
"Bolton")
, (Int
31964,Text
"Murillo")
, (Int
31940,Text
"Lutz")
, (Int
31896,Text
"Duarte")
, (Int
31886,Text
"Kidd")
, (Int
31882,Text
"Key")
, (Int
31860,Text
"Cooke")
]