Given a character string (which may be empty, or have a length of zero characters):
Use (at least) these five test values (strings):
Show all output here on this page.
F processString(input) [Char = Int] charMap V dup = Char("\0") V index = 0 V pos1 = -1 V pos2 = -1 L(key) input index++ I key C charMap dup = key pos1 = charMap[key] pos2 = index L.break charMap[key] = index V unique = I dup == Char("\0") {‘yes’} E ‘no’ V diff = I dup == Char("\0") {‘’} E ‘'’dup‘'’ V hexs = I dup == Char("\0") {‘’} E hex(dup.code) V position = I dup == Char("\0") {‘’} E pos1‘ ’pos2 print(‘#<40 #<6 #<10 #<8 #<3 #<5’.format(input, input.len, unique, diff, hexs, position))print(‘#<40 #2 #10 #8 #. #.’.format(‘String’, ‘Length’, ‘All Unique’, ‘1st Diff’, ‘Hex’, ‘Positions’))print(‘#<40 #2 #10 #8 #. #.’.format(‘------------------------’, ‘------’, ‘----------’, ‘--------’, ‘---’, ‘---------’))L(s) [‘’, ‘.’, ‘abcABC’, ‘XYZ ZYX’, ‘1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ’] processString(s)
String Length All Unique 1st Diff Hex Positions------------------------ ------ ---------- -------- --- --------- 0 yes . 1 yes abcABC 6 yes XYZ ZYX 7 no 'Z' 5A 3 5 1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ 36 no '0' 30 10 25
PROC PrintBH(BYTE a) BYTE ARRAY hex=['0 '1 '2 '3 '4 '5 '6 '7 '8 '9 'A 'B 'C 'D 'E 'F] Put(hex(a RSH 4)) Put(hex(a&$0F))RETURNPROC Test(CHAR ARRAY s) BYTE i,j,n,pos1,pos2 pos1=0 pos2=0 n=s(0)-1 IF n=255 THEN n=0 FI FOR i=1 TO n DO FOR j=i+1 TO s(0) DO IF s(j)=s(i) THEN pos1=i pos2=j EXIT FI OD IF pos1#0 THEN EXIT FI OD PrintF("""%S"" (len=%B) -> ",s,s(0)) IF pos1=0 THEN PrintE("all characters are unique.") ELSE PrintF("""%C"" (hex=$",s(pos1)) PrintBH(s(pos1)) PrintF(") is duplicated at pos. %B and %B.%E",pos1,pos2) FI PutE()RETURNPROC Main() Test("") Test(".") Test("abcABC") Test("XYZ ZYX") Test("1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ")RETURN
Screenshot from Atari 8-bit computer
"" (len=0) -> all characters are unique."." (len=1) -> all characters are unique."abcABC" (len=6) -> all characters are unique."XYZ ZYX" (len=7) -> "X" (hex=$58) is duplicated at pos. 1 and 7."1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (len=36) -> "0" (hex=$30) is duplicated at pos. 10 and 25.
withAda.Integer_Text_IO;useAda.Integer_Text_IO;withAda.Text_IO;useAda.Text_IO;procedureTest_All_Chars_UniqueisprocedureAll_Chars_Unique(S:inString)isbeginPut_Line("Input = """&S&""", length ="&S'Length'Image);forIinS'First..S'Last-1loopforJinI+1..S'LastloopifS(I)=S(J)thenPut(" First duplicate at positions"&I'Image&" and"&J'Image&", character = '"&S(I)&"', hex = ");Put(Character'Pos(S(I)),Width=>0,Base=>16);New_Line;return;endif;endloop;endloop;Put_Line(" All characters are unique.");endAll_Chars_Unique;beginAll_Chars_Unique("");All_Chars_Unique(".");All_Chars_Unique("abcABC");All_Chars_Unique("XYZ ZYX");All_Chars_Unique("1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ");endTest_All_Chars_Unique;
Input = "", length = 0 All characters are unique.Input = ".", length = 1 All characters are unique.Input = "abcABC", length = 6 All characters are unique.Input = "XYZ ZYX", length = 7 First duplicate at positions 1 and 7, character = 'X', hex = 16#58#Input = "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ", length = 36 First duplicate at positions 10 and 25, character = '0', hex = 16#30#
BEGIN # mode to hold the positions of duplicate characters in a string # MODE DUPLICATE = STRUCT( INT original, first duplicate ); # finds the first non-unique character in s and returns its position # # and the position of the original character in a DUPLICATE # # if all characters in s are uniue, returns LWB s - 1, UPB s + 1 # PROC first duplicate position = ( STRING s )DUPLICATE: BEGIN BOOL all unique := TRUE; INT o pos := LWB s - 1; INT d pos := UPB s + 1; FOR i FROM LWB s TO UPB s WHILE all unique DO FOR j FROM i + 1 TO UPB s WHILE all unique DO IF NOT ( all unique := s[ i ] /= s[ j ] ) THEN o pos := i; d pos := j FI OD OD; DUPLICATE( o pos, d pos ) END # first duplicate position # ; # task test cases # []STRING tests = ( "", ".", "abcABC", "XYZ ZYX", "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" ); FOR t pos FROM LWB tests TO UPB tests DO IF STRING s = tests[ t pos ]; DUPLICATE d = first duplicate position( s ); print( ( "<<<", s, ">>> (length ", whole( ( UPB s + 1 ) - LWB s, 0 ), "): " ) ); original OF d < LWB s THEN print( ( " all characters are unique", newline ) ) ELSE # have at least one duplicate # print( ( " first duplicate character: """, s[ original OF d ], """" , " at: ", whole( original OF d, 0 ), " and ", whole( first duplicate OF d, 0 ) , newline ) ) FI ODEND
<<<>>> (length 0): all characters are unique<<<.>>> (length 1): all characters are unique<<<abcABC>>> (length 6): all characters are unique<<<XYZ ZYX>>> (length 7): first duplicate character: "X" at: 1 and 7<<<1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ>>> (length 36): first duplicate character: "0" at: 10 and 25
Following AppleScript's convention of one-based indices:
useAppleScriptversion"2.4"useframework"Foundation"usescriptingadditionsonrunscriptshowSourceon|λ|(s)quoted("'",s)&" ("&lengthofs&")"end|λ|endscriptscriptshowDuplicateon|λ|(mb)scriptgoon|λ|(tpl)set{c,ixs}totplquoted("'",c)&" at "&intercalate(", ",ixs)end|λ|endscriptmaybe("None",go,mb)end|λ|endscriptfTable("Indices (1-based) of any duplicated characters:\n",¬showSource,showDuplicate,¬duplicatedCharIndices,¬{"",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"})endrun------------------CHARACTER DUPLICATIONS--------------------- duplicatedCharIndices :: String -> Maybe (Char, [Int])onduplicatedCharIndices(s)scriptpositionRecordon|λ|(dct,c,i)setkto(idofc)asstringscriptadditionalon|λ|(xs)insertDict(k,xs&i,dct)end|λ|endscriptmaybe(insertDict(k,{i},dct),additional,lookupDict(k,dct))end|λ|endscriptscriptfirstDuplicationon|λ|(sofar,idxs)set{iCode,xs}toidxsif1<lengthofxsthenscriptearlieston|λ|(kxs)ifitem1ofxs<(item1of(item2ofkxs))thenJust({chr(iCode),xs})elsesofarendifend|λ|endscriptmaybe(Just({chr(iCode),xs}),earliest,sofar)elsesofarendifend|λ|endscriptfoldl(firstDuplication,Nothing(),¬assocs(foldl(positionRecord,{name:""},chars(s))))endduplicatedCharIndices--------------------------GENERIC---------------------------- Just :: a -> Maybe aonJust(x)-- Constructor for an inhabited Maybe (option type) value.-- Wrapper containing the result of a computation.{type:"Maybe",Nothing:false,Just:x}endJust-- Nothing :: Maybe aonNothing()-- Constructor for an empty Maybe (option type) value.-- Empty wrapper returned where a computation is not possible.{type:"Maybe",Nothing:true}endNothing-- Tuple (,) :: a -> b -> (a, b)onTuple(a,b)-- Constructor for a pair of values, possibly of two different types.{type:"Tuple",|1|:a,|2|:b,length:2}endTuple-- assocs :: Map k a -> [(k, a)]onassocs(m)scriptgoon|λ|(k)setmbtolookupDict(k,m)iftrue=|Nothing|ofmbthen{}else{{k,|Just|ofmb}}endifend|λ|endscriptconcatMap(go,keys(m))endassocs-- keys :: Dict -> [String]onkeys(rec)(current application's¬NSDictionary'sdictionaryWithDictionary:rec)'sallKeys()aslistendkeys-- chr :: Int -> Charonchr(n)characteridnendchr-- chars :: String -> [Char]onchars(s)charactersofsendchars-- compose (<<<) :: (b -> c) -> (a -> b) -> a -> concompose(f,g)scriptpropertymf:mReturn(f)propertymg:mReturn(g)on|λ|(x)mf's|λ|(mg's|λ|(x))end|λ|endscriptendcompose-- concatMap :: (a -> [b]) -> [a] -> [b]onconcatMap(f,xs)setlngtolengthofxssetaccto{}tellmReturn(f)repeatwithifrom1tolngsetacctoacc&(|λ|(itemiofxs,i,xs))endrepeatendtellreturnaccendconcatMap-- enumFromTo :: Int -> Int -> [Int]onenumFromTo(m,n)ifm≤nthensetlstto{}repeatwithifrommtonsetendoflsttoiendrepeatlstelse{}endifendenumFromTo-- foldl :: (a -> b -> a) -> a -> [b] -> aonfoldl(f,startValue,xs)tellmReturn(f)setvtostartValuesetlngtolengthofxsrepeatwithifrom1tolngsetvto|λ|(v,itemiofxs,i,xs)endrepeatreturnvendtellendfoldl-- fst :: (a, b) -> aonfst(tpl)ifclassoftplisrecordthen|1|oftplelseitem1oftplendifendfst-- fTable :: String -> (a -> String) -> (b -> String) -> (a -> b) -> [a] -> StringonfTable(s,xShow,fxShow,f,xs)setystomap(xShow,xs)setwtomaximum(map(my|length|,ys))scriptarrowedon|λ|(a,b)justifyRight(w,space,a)&" -> "&bend|λ|endscripts&linefeed&unlines(zipWith(arrowed,¬ys,map(compose(fxShow,f),xs)))endfTable-- insertDict :: String -> a -> Dict -> DictoninsertDict(k,v,rec)tellcurrent applicationtelldictionaryWithDictionary_(rec)ofitsNSMutableDictionaryitssetValue:vforKey:(kasstring)itasrecordendtellendtellendinsertDict-- intercalate :: String -> [String] -> Stringonintercalate(delim,xs)set{dlm,mytext item delimiters}to¬{mytext item delimiters,delim}setstrtoxsastextsetmytext item delimiterstodlmstrendintercalate-- justifyRight :: Int -> Char -> String -> StringonjustifyRight(n,cFiller,strText)ifn>lengthofstrTextthentext-nthru-1of((replicate(n,cFiller)astext)&strText)elsestrTextendifendjustifyRight-- length :: [a] -> Inton|length|(xs)setctoclassofxsiflistiscorstringiscthenlengthofxselse(2^29-1)-- (maxInt - simple proxy for non-finite)endifend|length|-- lookupDict :: a -> Dict -> Maybe bonlookupDict(k,dct)-- Just the value of k in the dictionary,-- or Nothing if k is not found.setcatocurrent applicationsetvto(ca'sNSDictionary'sdictionaryWithDictionary:dct)'sobjectForKey:kifmissing value≠vthenJust(item1of((ca'sNSArray'sarrayWithObject:v)aslist))elseNothing()endifendlookupDict-- map :: (a -> b) -> [a] -> [b]onmap(f,xs)-- The list obtained by applying f-- to each element of xs.tellmReturn(f)setlngtolengthofxssetlstto{}repeatwithifrom1tolngsetendoflstto|λ|(itemiofxs,i,xs)endrepeatreturnlstendtellendmap-- maximum :: Ord a => [a] -> aonmaximum(xs)scripton|λ|(a,b)ifaismissing valueorb>athenbelseaendifend|λ|endscriptfoldl(result,missing value,xs)endmaximum-- maybe :: b -> (a -> b) -> Maybe a -> bonmaybe(v,f,mb)-- The 'maybe' function takes a default value, a function, and a 'Maybe'-- value. If the 'Maybe' value is 'Nothing', the function returns the-- default value. Otherwise, it applies the function to the value inside-- the 'Just' and returns the result.ifNothingofmbthenvelsetellmReturn(f)to|λ|(Justofmb)endifendmaybe-- min :: Ord a => a -> a -> aonmin(x,y)ify<xthenyelsexendifendmin-- mReturn :: First-class m => (a -> b) -> m (a -> b)onmReturn(f)-- 2nd class handler function lifted into 1st class script wrapper.ifscriptisclassoffthenfelsescriptproperty|λ|:fendscriptendifendmReturn-- quoted :: Char -> String -> Stringonquoted(c,s)-- string flanked on both sides-- by a specified quote character.c&s&cendquoted-- Egyptian multiplication - progressively doubling a list, appending-- stages of doubling to an accumulator where needed for binary-- assembly of a target length-- replicate :: Int -> a -> [a]onreplicate(n,a)setoutto{}if1>nthenreturnoutsetdblto{a}repeatwhile(1<n)if0<(nmod2)thensetouttoout&dblsetnto(ndiv2)setdblto(dbl&dbl)endrepeatreturnout&dblendreplicate-- take :: Int -> [a] -> [a]-- take :: Int -> String -> Stringontake(n,xs)setctoclassofxsiflistiscthenif0<nthenitems1thrumin(n,lengthofxs)ofxselse{}endifelseifstringiscthenif0<nthentext1thrumin(n,lengthofxs)ofxselse""endifelseifscriptiscthensetysto{}repeatwithifrom1tonsetvto|λ|()ofxsifmissing valueisvthenreturnyselsesetendofystovendifendrepeatreturnyselsemissing valueendifendtake-- unlines :: [String] -> Stringonunlines(xs)-- A single string formed by the intercalation-- of a list of strings with the newline character.set{dlm,mytext item delimiters}to¬{mytext item delimiters,linefeed}setstrtoxsastextsetmytext item delimiterstodlmstrendunlines-- zip :: [a] -> [b] -> [(a, b)]onzip(xs,ys)zipWith(Tuple,xs,ys)endzip-- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]onzipWith(f,xs,ys)setlngtomin(|length|(xs),|length|(ys))if1>lngthenreturn{}setxs_totake(lng,xs)-- Allow for non-finitesetys_totake(lng,ys)-- generators like cycle etcsetlstto{}tellmReturn(f)repeatwithifrom1tolngsetendoflstto|λ|(itemiofxs_,itemiofys_)endrepeatreturnlstendtellendzipWith
Indices (1-based) of any duplicated characters: '' (0) -> None '.' (1) -> None 'abcABC' (6) -> None 'XYZ ZYX' (7) -> 'X' at 1, 7'1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ' (36) -> '0' at 10, 25
strings:["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ","01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X","hétérogénéité","🎆🎃🎇🎈","😍😀🙌💃😍🙌","🐠🐟🐡🦈🐬🐳🐋🐡"]loopstrings'str[chars:splitstrprints["\"" ++ str ++ "\""~"(size |size str|):"]if?chars=uniquechars->print"has no duplicates."else[seen:#[]done:falsei:0while[and?i<sizecharsnot?done][ch:chars\[i]if?not?key?seench[seen\[ch]:i]else[print~"has duplicate char `|ch|` on |get seen ch| and |i|"done:true]i:i+1]]]
"" (size 0): has no duplicates."." (size 1): has no duplicates."abcABC" (size 6): has no duplicates."XYZ ZYX" (size 7): has duplicate char `Z` on 2 and 4"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (size 36): has duplicate char `0` on 9 and 24"01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X" (size 39): has duplicate char `0` on 0 and 10"hétérogénéité" (size 13): has duplicate char `é` on 1 and 3"🎆🎃🎇🎈" (size 4): has no duplicates."😍😀🙌💃😍🙌" (size 6): has duplicate char `😍` on 0 and 4"🐠🐟🐡🦈🐬🐳🐋🐡" (size 8): has duplicate char `🐡` on 2 and 7
unique_characters(str){arr:=[],res:=""fori,vinStrSplit(str)arr[v]:=arr[v]?arr[v]","i:ifori,vinArrifInStr(v,",")res.=v"|"i" @ "v"`tHex = "format("{1:X}",Asc(i))"`n"Sort,res,Nres:=RegExReplace(res,"`am)^[\d,]+\|")res:=StrSplit(res,"`n").1return""""str"""`tlength = "StrLen(str)"`n"(res?"Duplicates Found:`n"res:"Unique Characters")}
Examples:
test:=["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"]fori,vintestMsgBox%unique_characters(v)return
Outputs:
""length = 0Unique Characters---------------------------"."length = 1Unique Characters---------------------------"abcABC"length = 6Duplicates Found:a @ 1,4Hex = 61---------------------------"XYZ ZYX"length = 7Duplicates Found:X @ 1,7Hex = 58---------------------------"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"length = 36Duplicates Found:0 @ 10,25Hex = 30---------------------------
# syntax: GAWK -f DETERMINE_IF_A_STRING_HAS_ALL_UNIQUE_CHARACTERS.AWKBEGIN{for(i=0;i<=255;i++){ord_arr[sprintf("%c",i)]=i}# build array[character]=ordinal_valuen=split(",.,abcABC,XYZ ZYX,1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ",arr,",")for(iinarr){width=max(width,length(arr[i]))}width+=2fmt="| %-*s | %-6s | %-10s | %-8s | %-3s | %-9s |\n"head1=head2=sprintf(fmt,width,"string","length","all unique","1st diff","hex","positions")gsub(/[^|\n]/,"-",head1)printf(head1head2head1)# column headingsfor(i=1;i<=n;i++){main(arr[i])}printf(head1)# column footingexit(0)}functionmain(str,c,hex,i,leng,msg,position1,position2,tmp_arr){msg="yes"leng=length(str)for(i=1;i<=leng;i++){c=substr(str,i,1)if(cintmp_arr){msg="no"first_diff="'"c"'"hex=sprintf("%2X",ord_arr[c])position1=index(str,c)position2=ibreak}tmp_arr[c]=""}printf(fmt,width,"'"str"'",leng,msg,first_diff,hex,position1" "position2)}functionmax(x,y){return((x>y)?x:y)}
|----------------------------------------|--------|------------|----------|-----|-----------|| string | length | all unique | 1st diff | hex | positions ||----------------------------------------|--------|------------|----------|-----|-----------|| '' | 0 | yes | | | || '.' | 1 | yes | | | || 'abcABC' | 6 | yes | | | || 'XYZ ZYX' | 7 | no | 'Z' | 5A | 3 5 || '1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ' | 36 | no | '0' | 30 | 10 25 ||----------------------------------------|--------|------------|----------|-----|-----------|
subroutineCaracteresUnicos(cad$)lngt=length(cad$)print'Cadena = "'; cad$; '", longitud = '; lngtfori=1tolngtforj=i+1tolngtifmid(cad$,i,1)=mid(cad$,j,1)thenprint" Primer duplicado en las posiciones "&i&" y "&j&", caracter = '"&mid(cad$,i,1)&"', valor hex = "&tohex(asc(mid(cad$,i,1)))returnendifnextjnextiprint" Todos los caracteres son unicos."&chr(10)endsubroutinecallCaracteresUnicos("")callCaracteresUnicos(".")callCaracteresUnicos("abcABC")callCaracteresUnicos("XYZ ZYX")callCaracteresUnicos("1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ")
Similar as FreeBASIC entry.
100cls110subcaracteresunicos(cad$)120lngt=len(cad$)130print'Cadena = "';cad$;'" longitud = ';lngt140fori=1tolngt150forj=i+1tolngt160ifmid$(cad$,i,1)=mid$(cad$,j,1)then170print" Primer duplicado en las posiciones ";i;" y ";j;", caracter = '";mid$(cad$,i,1);"', valor hex = ";hex$(asc(mid$(cad$,i,1)))180print190exitsub200endif210nextj220nexti230print" Todos los caracteres son unicos.";chr$(10)240endsub250caracteresunicos("")260caracteresunicos(".")270caracteresunicos("abcABC")280caracteresunicos("XYZ ZYX")290caracteresunicos("1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ")300end
Same as FreeBASIC entry.
SubCaracteresUnicos(cadAsString)DimAsIntegerlngt=Len(cad)Print"Cadena = """;cad;""", longitud = ";lngtForiAsInteger=1TolngtForjAsInteger=i+1TolngtIfMid(cad,i,1)=Mid(cad,j,1)ThenPrint" Primer duplicado en las posiciones "&i&_" y "&j&", caracter = '"&Mid(cad,i,1)&_"', valor hex = "&Hex(Asc(Mid(cad,i,1)))PrintExitSubEndIfNextjNextiPrint" Todos los caracteres son unicos."&Chr(10)EndSubCaracteresUnicos("")CaracteresUnicos(".")CaracteresUnicos("abcABC")CaracteresUnicos("XYZ ZYX")CaracteresUnicos("1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ")Sleep
Cadena = "", longitud = 0 Todos los caracteres son unicos.Cadena = ".", longitud = 1 Todos los caracteres son unicos.Cadena = "abcABC", longitud = 6 Todos los caracteres son unicos.Cadena = "XYZ ZYX", longitud = 7 Primer duplicado en las posiciones 1 y 7, caracter = 'X', valor hex = 58Cadena = "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ", longitud = 36 Primer duplicado en las posiciones 10 y 25, caracter = '0', valor hex = 30
ProcedureCaracteresUnicos(cad.s)lngt.i=Len(cad)PrintN("Cadena = '"+cad+"' longitud = "+Str(lngt))Fori.i=1TolngtForj.i=i+1TolngtIfMid(cad,i,1)=Mid(cad,j,1)PrintN(" Primer duplicado en las posiciones "+Str(i)+" y "+Str(j)+", caracter = '"+Mid(cad,i,1)+"', valor hex = "+Hex(Asc(Mid(cad,i,1))))ProcedureReturnEndIfNextNextPrintN(" Todos los caracteres son unicos.")EndProcedureOpenConsole()CaracteresUnicos("")CaracteresUnicos(".")CaracteresUnicos("abcABC")CaracteresUnicos("XYZ ZYX")CaracteresUnicos("1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ")PrintN(#CRLF$+"--- Press ENTER to exit ---"):Input()CloseConsole()
Similar as FreeBASIC entry.
ModuleModule1SubMain()Diminput()={"",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"}ForEachsIninputConsole.WriteLine($"'{s}' (Length {s.Length}) "+String.Join(", ",s.Select(Function(c,i)(c,i)).GroupBy(Function(t)t.c).Where(Function(g)g.Count()>1).Select(Function(g)$"'{g.Key}' (0X{AscW(g.Key):X})[{String.Join(",", g.Select(Function(t) t.i))}]").DefaultIfEmpty("All characters are unique.")))NextEndSubEndModule
'' (Length 0) All characters are unique.'.' (Length 1) All characters are unique.'abcABC' (Length 6) All characters are unique.'XYZ ZYX' (Length 7) 'X' (0X58)[0, 6], 'Y' (0X59)[1, 5], 'Z' (0X5A)[2, 4]'1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ' (Length 36) '0' (0X30)[9, 24]
subcaracteresunicos(cad$)locallngt,i,jlngt=len(cad$)print"cadena = \"", cad$, "\", longitud = ",lngtfori=1tolngtforj=i+1tolngtifmid$(cad$,i,1)=mid$(cad$,j,1)thenprint" Primer duplicado en las posiciones ",i," y ",j,", caracter = \'",mid$(cad$,i,1),"\', valor hex = ",hex$(asc(mid$(cad$,i,1)))printreturnendifnextjnextiprint" Todos los caracteres son unicos.\n"endsubcaracteresunicos("")caracteresunicos(".")caracteresunicos("abcABC")caracteresunicos("XYZ ZYX")caracteresunicos("1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ")
Same as FreeBASIC entry.
O(n^2) method used for finding indices.
Hex function and loop similar toDetermine if a string has all the same characters
Check←=⌜˜Hex←⊏⟜(∾"0A"+⟜↕¨10‿26)16{⌽𝕗|⌊∘÷⟜𝕗⍟(↕1+·⌊𝕗⋆⁼1⌈⊢)}{𝕊str:r←Checkstr•Out{∧´1=+´˘r?"All characters are unique";i←/⊏(1<+´˘r)/rch←(⊑i)⊑str"'"∾ch∾"' (hex: "∾(Hexch-@)∾", indices: "∾(•Fmti)∾") duplicated in string '"∾str∾"'"}}¨⟨""".""abcABC""XYZ ZYX""1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"⟩
All characters are uniqueAll characters are uniqueAll characters are unique'X' (hex: 58, indices: ⟨ 0 7 ⟩) duplicated in string 'XYZ ZYX''0' (hex: 30, indices: ⟨ 9 24 ⟩) duplicated in string '1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ'
#include<stdio.h>#include<stdlib.h>#include<string.h>/** return -1 if s has no repeated characters, otherwise the array* index where a duplicated character first reappears*/intuniquechars(char*s){inti,j,slen;slen=strlen(s);if(slen<2)return-1;for(i=0;i<(slen-1);i++)for(j=i+1;j<slen;j++)if(s[i]==s[j])returnj;return-1;}voidreport(char*s){intpos,first;pos=uniquechars(s);if(pos==-1)printf("\"%s\" (length = %d) has no duplicate characters\n",s,strlen(s));else{printf("\"%s\" (length = %d) has duplicate characters:\n",s,strlen(s));/* find first instance of duplicated ch in s */first=(int)(strchr(s,s[pos])-s);printf(" '%c' (= %2Xh) appears at positions %d and %d\n",s[pos],s[pos],first+1,pos+1);}}intmain(void){report("");report(".");report("abcABC");report("XYZ ZYX");report("1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ");returnEXIT_SUCCESS;}
The reported character positions are indexed from 1, the way non-programmers normally count!
"" (length = 0) has no duplicate characters"." (length = 1) has no duplicate characters"abcABC" (length = 6) has no duplicate characters"XYZ ZYX" (length = 7) has duplicate characters: 'X' (= 58h) appears at positions 1 and 7"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (length = 36) has duplicate characters: '0' (= 30h) appears at positions 10 and 25
usingSystem;usingSystem.Linq;publicclassProgram{staticvoidMain{string[]input={"",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"};foreach(stringsininput){Console.WriteLine($"\"{s}\" (Length {s.Length}) "+string.Join(", ",s.Select((c,i)=>(c,i)).GroupBy(t=>t.c).Where(g=>g.Count()>1).Select(g=>$"'{g.Key}' (0X{(int)g.Key:X})[{string.Join(",", g.Select(t => t.i))}]").DefaultIfEmpty("All characters are unique.")));}}}
"" (Length 0) All characters are unique."." (Length 1) All characters are unique."abcABC" (Length 6) All characters are unique."XYZ ZYX" (Length 7) 'X'(0X58) [0, 6], 'Y'(0X59) [1, 5], 'Z'(0X5A) [2, 4]"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (Length 36) '0'(0X30) [9, 24]
#include<iostream>#include<string>voidstring_has_repeated_character(conststd::string&str){size_tlen=str.length();std::cout<<"input:\""<<str<<"\", length: "<<len<<'\n';for(size_ti=0;i<len;++i){for(size_tj=i+1;j<len;++j){if(str[i]==str[j]){std::cout<<"String contains a repeated character.\n";std::cout<<"Character '"<<str[i]<<"' (hex "<<std::hex<<static_cast<unsignedint>(str[i])<<") occurs at positions "<<std::dec<<i+1<<" and "<<j+1<<".\n\n";return;}}}std::cout<<"String contains no repeated characters.\n\n";}intmain(){string_has_repeated_character("");string_has_repeated_character(".");string_has_repeated_character("abcABC");string_has_repeated_character("XYZ ZYX");string_has_repeated_character("1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ");return0;}
input: "", length: 0String contains no repeated characters.input: ".", length: 1String contains no repeated characters.input: "abcABC", length: 6String contains no repeated characters.input: "XYZ ZYX", length: 7String contains a repeated character.Character 'X' (hex 58) occurs at positions 1 and 7.input: "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ", length: 36String contains a repeated character.Character '0' (hex 30) occurs at positions 10 and 25.
(defnuniq-char-string[s](let[len(counts)](if(=len(count(sets)))(println(format"All %d chars unique in: '%s'"lens))(loop[prev-chars#{}idx0chars(vecs)](let[c(firstchars)](if(contains?prev-charsc)(println(format"'%s' (len: %d) has '%c' duplicated at idx: %d"slencidx))(recur(conjprev-charsc)(incidx)(restchars))))))))
All 0 chars unique in: ''All 1 chars unique in: '.'All 6 chars unique in: 'abcABC''XYZ ZYX' (len: 7) has 'Z' duplicated at idx: 4'1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ' (len: 36) has '0' duplicated at idx: 24All 4 chars unique in: 'asdf''asdfas' (len: 6) has 'a' duplicated at idx: 4'foofoo' (len: 6) has 'o' duplicated at idx: 2'foOfoo' (len: 6) has 'f' duplicated at idx: 3
;; * Loading the iterate library(eval-when(:compile-toplevel:load-toplevel)(ql:quickload'("iterate")));; * The package definition(defpackage:unique-string(:use:common-lisp:iterate))(in-package:unique-string);; * The test strings(defparametertest-strings'(""".""abcABC""XYZ ZYX""1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"));; * The function(defununique-string(string)"Returns T if STRING has all unique characters."(iter(withhash=(make-hash-table:test#'equal))(withlen=(lengthstring))(withresult=T)(forcharin-stringstring)(forposfrom0)(initially(formatt"String ~a of length ~D~%"stringlen))(if#1=(gethashcharhash);; The character was seen before(progn(formatt" --> Non-unique character ~c #X~X found at position ~D, before ~D ~%"char(char-codechar)pos#1#)(setfresultnil));; The character was not seen before, saving its position(setf#1#pos))(finally(whenresult(formatt" --> All characters are unique~%"))(returnresult))))(mapcar#'unique-stringtest-strings)
String of length 0 --> All characters are uniqueString . of length 1 --> All characters are uniqueString abcABC of length 6 --> All characters are uniqueString XYZ ZYX of length 7 --> Non-unique character Z #X5A found at position 4, before 2 --> Non-unique character Y #X59 found at position 5, before 1 --> Non-unique character X #X58 found at position 6, before 0 String 1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ of length 36 --> Non-unique character 0 #X30 found at position 24, before 9
importstd.stdio;voiduniqueCharacters(stringstr){writefln("input: `%s`, length: %d",str,str.length);foreach(i;0..str.length){foreach(j;i+1..str.length){if(str[i]==str[j]){writeln("String contains a repeated character.");writefln("Character '%c' (hex %x) occurs at positions %d and %d.",str[i],str[i],i+1,j+1);writeln;return;}}}writeln("String contains no repeated characters.");writeln;}voidmain(){uniqueCharacters("");uniqueCharacters(".");uniqueCharacters("abcABC");uniqueCharacters("XYZ ZYX");uniqueCharacters("1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ");}
input: ``, length: 0String contains no repeated characters.input: `.`, length: 1String contains no repeated characters.input: `abcABC`, length: 6String contains no repeated characters.input: `XYZ ZYX`, length: 7String contains a repeated character.Character 'X' (hex 58) occurs at positions 1 and 7.input: `1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ`, length: 36String contains a repeated character.Character '0' (hex 30) occurs at positions 10 and 25.
programDetermine_if_a_string_has_all_unique_characters;{$APPTYPE CONSOLE}usesSystem.SysUtils;procedurestring_has_repeated_character(str:string);varlen,i,j:Integer;beginlen:=length(str);Writeln('input: \',str,'\, length: ',len);fori:=1tolen-1dobeginforj:=i+1tolendobeginifstr[i]=str[j]thenbeginWriteln('String contains a repeated character.');Writeln('Character "',str[i],'" (hex ',ord(str[i]).ToHexString,') occurs at positions ',i+1,' and ',j+1,'.'#10);Exit;end;end;end;Writeln('String contains no repeated characters.'+sLineBreak);end;beginstring_has_repeated_character('');string_has_repeated_character('.');string_has_repeated_character('abcABC');string_has_repeated_character('XYZ ZYX');string_has_repeated_character('1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ');readln;end.
Delphi strings are start index in one.
input: \\, length: 0String contains no repeated characters.input: \.\, length: 1String contains no repeated characters.input: \abcABC\, length: 6String contains no repeated characters.input: \XYZ ZYX\, length: 7String contains a repeated character.Character "X" (hex 0058) occurs at positions 2 and 8.input: \1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ\, length: 36String contains a repeated character.Character "0" (hex 0030) occurs at positions 11 and 26.
createorreplacetablestringsasvalues(''),('.'),('abcABC'),('XYZ ZYX'),('1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ'),('😍😀🙌💃😍🙌');createorreplacefunctionlist_all_distinct(lst)as(length(lst)=length(list_distinct(lst)));#Return{n,m}wherenandmarerespectivelythefirstandsecondindicesofthe#firstnon-uniquecharacterinstr,IO=1,elseNULLcreateorreplacefunctiondescribe_first_duplicate(str)as(withrecursivecteas(selectstr[1]asc,2asn,0asmunionallselectstr[n]asc,n+1asn,position(cinstr[n:])asmfromctewherem=0andn<=length(str))select{n:(n-2),m:(m+n-2)}fromctewherem!=0limit1);##Thetask:WITHcteas(selectstring,describe_first_duplicate(string)asfirst_duplicatefromstringst(string))selectstring,length(string)aslength,if(first_duplicateisnull,null,string[first_duplicate['n']])as"duplicated",if(first_duplicateisnull,null,hex(string[first_duplicate['n']]))as"hex",first_duplicateas"first two indices"fromcte;
┌───────────────────────────────┬────────┬────────────┬──────────┬──────────────────────────────┐│ string │ length │ duplicated │ hex │ first two indices ││ varchar │ int64 │ varchar │ varchar │ struct(n integer, m integer) │├───────────────────────────────┼────────┼────────────┼──────────┼──────────────────────────────┤│ │ 0 │ │ │ ││ . │ 1 │ │ │ ││ abcABC │ 6 │ │ │ ││ XYZ ZYX │ 7 │ X │ 58 │ {'n': 1, 'm': 7} ││ 1234567890ABCDEFGHIJKLMN0PQ… │ 36 │ 0 │ 30 │ {'n': 10, 'm': 25} ││ 😍😀🙌💃😍🙌 │ 6 │ 😍 │ F09F988D │ {'n': 1, 'm': 5} │└───────────────────────────────┴────────┴────────────┴──────────┴──────────────────────────────┘
func$ hex h . for d in [ h div 16 h mod 16 ] if d > 9 : d += 7 h$ &= strchar (d + 48) . return h$.proc unichar s$ . len d[] 65536 s$[] = strchars s$ for i to len s$[] h = strcode s$[i] if d[h] <> 0 write " --> duplicates: '" & s$[i] & "' (" & hex h & "h)" print "' positions: " & d[h] & ", " & i return . d[h] = i . print "ok".repeat s$ = input until s$ = "EOF" print "'" & s$ & "'" & " length " & len s$ unichar s$ print "".input_data.abcABCXYZ ZYX1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZEOF
'' length 0ok'.' length 1ok'abcABC' length 6ok'XYZ ZYX' length 7 --> duplicates: 'Z' (5Ah)' positions: 3, 5'1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ' length 36 --> duplicates: '0' (30h)' positions: 10, 25
# by Artyom BologovHg/^\(.*\)\(.\)\(.*\)\2\(.*\)$/s//"\1\2\3\2\4" is not unique, repeating '\2'/v/ is not unique, repeating /s/.*/"&" is unique/,pQ
$ ed -s all-unique.input < all-unique.ed Newline appended"" is unique"." is unique"abcABC" is unique"XYZ ZYX" is not unique, repeating ' '"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" is not unique, repeating '0'
-module(string_examples).-export([all_unique/1,all_unique_examples/0]).all_unique(String)->CharPosPairs=lists:zip(String,lists:seq(1,length(String))),Duplicates=[{Char1,Pos1,Pos2}||{Char1,Pos1}<-CharPosPairs,{Char2,Pos2}<-CharPosPairs,Char1=:=Char2,Pos2>Pos1],caseDuplicatesof[]->all_unique;[{Char,P1,P2}|_]->{not_all_unique,Char,P1,P2}end.all_unique_examples()->lists:foreach(fun(Str)->io:format("String\"~ts\" (length~p): ",[Str,length(Str)]),caseall_unique(Str)ofall_unique->io:format("All characters unique.~n");{not_all_unique,Char,P1,P2}->io:format("First duplicate is '~tc' (0x~.16b)"" at positions~p and~p.~n",[Char,Char,P1,P2])endend,["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"]).
$ erlErlang/OTP 23 [erts-11.1.8] [source] [64-bit] [smp:12:12] [ds:12:12:10] [async-threads:1]Eshell V11.1.8 (abort with ^G)1> c(string_examples).{ok,string_examples}2> string_examples:all_unique_examples().String "" (length 0): All characters unique.String "." (length 1): All characters unique.String "abcABC" (length 6): All characters unique.String "XYZ ZYX" (length 7): First duplicate is 'X' (0x58) at positions 1 and 7.String "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (length 36): First duplicate is '0' (0x30) at positions 10 and 25.ok
// Determine if a string has all unique characters. Nigel Galloway: June 9th., 2020letfN(n:string)=n.ToCharArray()|>Array.mapi(funng->(n,g))|>Array.groupBy(fun(_,n)->n)|>Array.filter(fun(_,n)->n.Length>1)letallUniquen=matchfNnwithgwheng.Length=0->printfn"All charcters in <<<%s>>> (length %d) are unique"nn.Length|g->Array.iter(fun(n,g)->printf"%A is repeated at positions"n;Array.iter(fun(n,_)->printf" %d"n)g;printf" ")gprintfn"in <<<%s>>> (length %d)"nn.LengthallUnique""allUnique"."allUnique"abcABC"allUnique"XYZ ZYX"allUnique"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"
All charcters in <<<>>> (length 0) are uniqueAll charcters in <<<.>>> (length 1) are uniqueAll charcters in <<<abcABC>>> (length 6) are unique'X' is repeated at positions 0 6 'Y' is repeated at positions 1 5 'Z' is repeated at positions 2 4 in <<<XYZ ZYX>>> (length 7)'0' is repeated at positions 9 24 in <<<1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ>>> (length 36)
USING:formattingfrygeneralizationsiokernelmath.parsersequencessets;:repeated(eltseq--)[dup>hexover]dipindicesfirst2" '%c' (0x%s) at indices %d and %d.\n"printf;:uniqueness-report(str--)dupduplength"%u — length %d — contains "printf[duplicates]keepoverempty?[2drop"all unique characters."print]["repeated characters:"print'[_repeated]each]if;""".""abcABC""XYZ ZYX""1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"[uniqueness-reportnl]5napply
"" — length 0 — contains all unique characters."." — length 1 — contains all unique characters."abcABC" — length 6 — contains all unique characters."XYZ ZYX" — length 7 — contains repeated characters: 'Z' (0x5a) at indices 2 and 4. 'Y' (0x59) at indices 1 and 5. 'X' (0x58) at indices 0 and 6."1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" — length 36 — contains repeated characters: '0' (0x30) at indices 9 and 24.
programdemo_verifyimplicit none callnodup('')callnodup('.')callnodup('abcABC')callnodup('XYZ ZYX')callnodup('1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ')containssubroutinenodup(str)character(len=*),intent(in)::strcharacter(len=*),parameter::g='(*(g0))'character(len=:),allocatable::chinteger::whereinteger::iwhere=0ch=''doi=1,len(str)-1ch=str(i:i)where=index(str(i+1:),ch)if(where.ne.0)then where=where+iexit endif enddo if(where.eq.0)then write(*,g)'STR: "',str,'"',new_line('a'),'LEN: ',len(str),'. No duplicate characters found'else write(*,g)'STR: "',str,'"'write(*,'(a,a,t1,a,a)')repeat(' ',where+5),'^',repeat(' ',i+5),'^'write(*,g)'LEN: ',len(str),&&'. Duplicate chars. First duplicate at positions ',i,' and ',where,&&' where a ','"'//str(where:where)//'"(hex:',hex(str(where:where)),') was found.'endif write(*,*)end subroutinenodupfunctionhex(ch)result(hexstr)character(len=1),intent(in)::chcharacter(len=:),allocatable::hexstrhexstr=repeat(' ',100)write(hexstr,'(Z0)')chhexstr=trim(hexstr)end functionhexend programdemo_verify
STR: ""LEN: 0. No duplicate characters foundSTR: "."LEN: 1. No duplicate characters foundSTR: "abcABC"LEN: 6. No duplicate characters foundSTR: "XYZ ZYX" ^ ^LEN: 7. Duplicate chars. First duplicate at positions 1 and 7 where a "X"(hex:58) was found.STR: "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" ^ ^LEN: 36. Duplicate chars. First duplicate at positions 10 and 25 where a "0"(hex:30) was found.
void local fn StringHasUniqueCharacters( string as CFStringRef ) long i, j, length = len( string ) if length == 0 then printf @"The string \"\" is empty and thus has no characters to compare.\n" : exit fn printf @"The string: \"%@\" has %ld characters.", string, length for i = 0 to length - 1 for j = i + 1 to length - 1 if ( fn StringIsEqual( mid( string, i, 1 ), mid( string, j, 1 ) ) ) CFStringRef duplicate = mid( string, i, 1 ) printf @"The first duplicate character, \"%@\", is found at positions %ld and %ld.", duplicate, i, j printf @"The hex value of \"%@\" is: 0X%x\n", duplicate, fn StringCharacterAtIndex( duplicate, 0 ) exit fn end if next next printf @"All characters in string are unique.\n"end fnfn StringHasUniqueCharacters( @"" )fn StringHasUniqueCharacters( @"." )fn StringHasUniqueCharacters( @"abcABC" )fn StringHasUniqueCharacters( @"XYZ ZYX" )fn StringHasUniqueCharacters( @"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" )HandleEvents
The string "" is empty and thus has no characters to compare.The string: "." has 1 characters.All characters in string are unique.The string: "abcABC" has 6 characters.All characters in string are unique.The string: "XYZ ZYX" has 7 characters.The first duplicate character, "X", is found at positions 0 and 6.The hex value of "X" is: 0X58The string: "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" has 36 characters.The first duplicate character, "0", is found at positions 9 and 24.The hex value of "0" is: 0X30
packagemainimport"fmt"funcanalyze(sstring){chars:=[]rune(s)le:=len(chars)fmt.Printf("Analyzing %q which has a length of %d:\n",s,le)ifle>1{fori:=0;i<le-1;i++{forj:=i+1;j<le;j++{ifchars[j]==chars[i]{fmt.Println(" Not all characters in the string are unique.")fmt.Printf(" %q (%#[1]x) is duplicated at positions %d and %d.\n\n",chars[i],i+1,j+1)return}}}}fmt.Println(" All characters in the string are unique.\n")}funcmain(){strings:=[]string{"",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ","01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X","hétérogénéité","🎆🎃🎇🎈","😍😀🙌💃😍🙌","🐠🐟🐡🦈🐬🐳🐋🐡",}for_,s:=rangestrings{analyze(s)}}
Analyzing "" which has a length of 0: All characters in the string are unique.Analyzing "." which has a length of 1: All characters in the string are unique.Analyzing "abcABC" which has a length of 6: All characters in the string are unique.Analyzing "XYZ ZYX" which has a length of 7: Not all characters in the string are unique. 'X' (0x58) is duplicated at positions 1 and 7.Analyzing "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" which has a length of 36: Not all characters in the string are unique. '0' (0x30) is duplicated at positions 10 and 25.Analyzing "01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X" which has a length of 39: Not all characters in the string are unique. '0' (0x30) is duplicated at positions 1 and 11.Analyzing "hétérogénéité" which has a length of 13: Not all characters in the string are unique. 'é' (0xe9) is duplicated at positions 2 and 4.Analyzing "🎆🎃🎇🎈" which has a length of 4: All characters in the string are unique.Analyzing "😍😀🙌💃😍🙌" which has a length of 6: Not all characters in the string are unique. '😍' (0x1f60d) is duplicated at positions 1 and 5.Analyzing "🐠🐟🐡🦈🐬🐳🐋🐡" which has a length of 8: Not all characters in the string are unique. '🐡' (0x1f421) is duplicated at positions 3 and 8.
classStringUniqueCharacters{staticvoidmain(String[]args){printf("%-40s %2s %10s %8s %s %s%n","String","Length","All Unique","1st Diff","Hex","Positions")printf("%-40s %2s %10s %8s %s %s%n","------------------------","------","----------","--------","---","---------")for(Strings:["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"]){processString(s)}}privatestaticvoidprocessString(Stringinput){Map<Character,Integer>charMap=newHashMap<>()chardup=0intindex=0intpos1=-1intpos2=-1for(charkey:input.toCharArray()){index++if(charMap.containsKey(key)){dup=keypos1=charMap.get(key)pos2=indexbreak}charMap.put(key,index)}Stringunique=(int)dup==0?"yes":"no"Stringdiff=(int)dup==0?"":"'"+dup+"'"Stringhex=(int)dup==0?"":Integer.toHexString((int)dup).toUpperCase()Stringposition=(int)dup==0?"":pos1+" "+pos2printf("%-40s %-6d %-10s %-8s %-3s %-5s%n",input,input.length(),unique,diff,hex,position)}}
String Length All Unique 1st Diff Hex Positions------------------------ ------ ---------- -------- --- --------- 0 yes . 1 yes abcABC 6 yes XYZ ZYX 7 no 'Z' 5A 3 5 1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ 36 no '0' 30 10 25
importData.List(groupBy,intersperse,sort,transpose)importData.Char(ord,toUpper)importData.Function(on)importNumeric(showHex)hexFromChar::Char->StringhexFromCharc=maptoUpper$showHex(ordc)""string::String->Stringstringxs=('\"' : xs) <> "\""char::Char->Stringcharc=['\'',c,'\'']size::String->Stringsize=show.lengthpositions::(Int,Int)->Stringpositions(a,b)=showa<>" "<>showbforTable::String->[String]forTablexs=stringxs:go(allUniquexs)wheregoNothing=[sizexs,"yes","","",""]go(Just(u,ij))=[sizexs,"no",charu,hexFromCharu,positionsij]showTable::Bool->Char->Char->Char->[[String]]->StringshowTable____[]=[]showTableheaderverhorsepcontents=unlines$hr:(ifheaderthenz:hr:zselseinterspersehrzss)<>[hr]wherevss=map(maplength)contentsms=mapmaximum(transposevss)::[Int]hr=concatMap(\n->sep:replicatenhor)ms<>[sep]top=replicate(lengthhr)horbss=map(map(`replicate`' ').zipWith(-)ms)vsszss@(z:zs)=zipWith(\usbs->concat(zipWith(\xy->(ver:x)<>y)usbs)<>[ver])contentsbsstablexs=showTableTrue'|''-''+'(["string","length","all unique","1st diff","hex","positions"]:mapforTablexs)allUnique::(Ordb,Orda,Numb,Enumb)=>[a]->Maybe(a,(b,b))allUniquexs=go.groupBy(on(==)fst).sort.zipxs$[0..]wherego[]=Nothinggo([_]:us)=gousgo(((u,i):(_,j):_):_)=Just(u,(i,j))main::IO()main=putStrLn$table["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"]
+--------------------------------------+------+----------+--------+---+---------+|string |length|all unique|1st diff|hex|positions|+--------------------------------------+------+----------+--------+---+---------+|"" |0 |yes | | | ||"." |1 |yes | | | ||"abcABC" |6 |yes | | | ||"XYZ ZYX" |7 |no |'X' |58 |0 6 ||"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"|36 |no |'0' |30 |9 24 |+--------------------------------------+------+----------+--------+---+---------+
Alternatively, defining a duplicatedCharIndices function in terms of sortOn, groupBy, and filter:
importData.List(groupBy,intercalate,sortOn)importData.Function(on)importNumeric(showHex)importData.Char(ord)------------- INDICES OF DUPLICATED CHARACTERS -----------duplicatedCharIndices::String->Maybe(Char,[Int])duplicatedCharIndicess|nullduplicates=Nothing|otherwise=Just$((,).(snd.head)<*>fmapfst)(head(sortOn(fst.head)duplicates))whereduplicates=filter((1<).length)$groupBy(on(==)snd)$sortOnsnd$zip[0..]s--------------------------- TEST -------------------------main::IO()main=putStrLn$fTable"First duplicated character, if any:"(fmap(<>)show<*>((" ("<>).(<>")").show.length))(maybe"None"(\(c,ixs)->unwords[showc,"(0x"<>showHex(ordc)") at",intercalate", "(show<$>ixs)]))duplicatedCharIndices["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"]------------------------- DISPLAY ------------------------fTable::String->(a->String)->(b->String)->(a->b)->[a]->StringfTablesxShowfxShowfxs=unlines$s:fmap(((<>).rjustw' '.xShow)<*>((" -> "<>).fxShow.f))xswhererjustnc=drop.length<*>(replicatenc<>)w=maximum(length.xShow<$>xs)
First duplicated character, if any: "" (0) -> None "." (1) -> None "abcABC" (6) -> None "XYZ ZYX" (7) -> 'X' (0x58) at 0, 6"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (36) -> '0' (0x30) at 9, 24
Or, as an alternative to grouping and sorting – folding a string down to a Map of indices:
importqualifiedSafeasSimportqualifiedData.Map.StrictasMimportData.List(intercalate,foldl')--'importData.Ord(comparing)importNumeric(showHex)importData.Char(ord)----------- INDICES OF ANY DUPLICATED CHARACTERS ---------duplicatedCharIndices::String->Maybe(Char,[Int])duplicatedCharIndicesxs=S.minimumByMay(comparing(head.snd))(M.toList(M.filter((1<).length)(foldl'--'(\a(i,c)->M.insertc(maybe[i](<>[i])(M.lookupca))a)M.empty(zip[0..]xs))))-- OR, fusing filter, toList, and minimumByMay down to a single fold:duplicatedCharIndices_::String->Maybe(Char,[Int])duplicatedCharIndices_xs=M.foldrWithKeygoNothing(foldl'--'(\a(i,c)->M.insertc(maybe[i](<>[i])(M.lookupca))a)M.empty(zip[0..]xs))wheregok[_]mb=mb-- UniquegokxsNothing=Just(k,xs)-- Duplicatedgokxs@(x:_)(Just(c,ys@(y:_)))|x<y=Just(k,xs)-- Earlier duplication|otherwise=Just(c,ys)--------------------------- TEST -------------------------main::IO()main=putStrLn$fTable"First duplicated character, if any:"((<>)<$>show<*>((" ("<>).(<>")").show.length))(maybe"None"(\(c,ixs)->unwords[showc,"(0x"<>showHex(ordc)") at",intercalate", "(show<$>ixs)]))duplicatedCharIndices_["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"]------------------------- DISPLAY ------------------------fTable::String->(a->String)->(b->String)->(a->b)->[a]->StringfTablesxShowfxShowfxs=unlines$s:fmap(((<>).rjustw' '.xShow)<*>((" -> "<>).fxShow.f))xswhererjustnc=drop.length<*>(replicatenc<>)w=maximum(length.xShow<$>xs)
First duplicated character, if any: "" (0) -> None "." (1) -> None "abcABC" (6) -> None "XYZ ZYX" (7) -> 'X' (0x58) at 0, 6"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (36) -> '0' (0x30) at 9, 24
Quotes surround the literals to make the computed one-at-a-time results present well in the combined table.
rc_unique=:monaddefinestring=.'"',y,'"'self_classification=.=yNB. deprecated- consumes space proportional to the squared tally of y (*: # y)is_unique=.self_classification=&#yif.is_uniquedo.(#y);string;'unique'else.duplicate_masks=.(#~(1<+/"1))self_classificationduplicate_characters=.~.y#~+./duplicate_masksASCII_values_of_duplicates=.a.i.duplicate_charactersmarkers=.duplicate_masks{' ^'A=.(#y);string,' ',.markersB=.'duplicate',ASCII_values_of_duplicates('<',(#~31&<)~,'> ASCII ',":@:[)"0duplicate_charactersA,<Bend.)
Tests include those of the C example and a pair of MS-DOS line terminations.
(;:'length string analysis') , rc_unique;._2';.;abcABC;XYZ YZX;1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ; ;2;333;.55;tttTTT;4444 444k;',(4$CRLF),';'┌──────┬──────────────────────────────────────┬─────────────┐│length│string │analysis │├──────┼──────────────────────────────────────┼─────────────┤│0 │"" │unique │├──────┼──────────────────────────────────────┼─────────────┤│1 │"." │unique │├──────┼──────────────────────────────────────┼─────────────┤│6 │"abcABC" │unique │├──────┼──────────────────────────────────────┼─────────────┤│7 │"XYZ YZX" │duplicate ││ │ ^ ^ │<X> ASCII 88 ││ │ ^ ^ │<Y> ASCII 89 ││ │ ^ ^ │<Z> ASCII 90 │├──────┼──────────────────────────────────────┼─────────────┤│36 │"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"│duplicate ││ │ ^ ^ │<0> ASCII 48 │├──────┼──────────────────────────────────────┼─────────────┤│3 │" " │duplicate ││ │ ^^^ │< > ASCII 32 │├──────┼──────────────────────────────────────┼─────────────┤│1 │"2" │unique │├──────┼──────────────────────────────────────┼─────────────┤│3 │"333" │duplicate ││ │ ^^^ │<3> ASCII 51 │├──────┼──────────────────────────────────────┼─────────────┤│3 │".55" │duplicate ││ │ ^^ │<5> ASCII 53 │├──────┼──────────────────────────────────────┼─────────────┤│6 │"tttTTT" │duplicate ││ │ ^^^ │<t> ASCII 116││ │ ^^^ │<T> ASCII 84 │├──────┼──────────────────────────────────────┼─────────────┤│9 │"4444 444k" │duplicate ││ │ ^^^^ ^^^ │<4> ASCII 52 │├──────┼──────────────────────────────────────┼─────────────┤│4 │" " │duplicate ││ │ ^ ^ │<> ASCII 13 ││ │ ^ ^ │<> ASCII 10 │└──────┴──────────────────────────────────────┴─────────────┘
More uniqueness tests with performance comparison
NB. unique_index answers "Do the left and right indexes match?"unique_index=:(i.-:i:)~assert01-:2unique_index\001NB. unique_set answers "Are lengths of the nub and original equal?"unique_set=:-:&#~.assert01-:_2unique_set\'aab'NB. unique_nubsieve answers "Are the items unique?"unique_nubsieve=:0-.@:e.~:assert01-:_2unique_nubsieve\'aab'Note'compared to nubsieve' the index method takes 131% longer and 15 times additional memory the set formation method 15% longer and uses 7 times additional memory.)
importjava.util.HashMap;importjava.util.Map;// Title: Determine if a string has all unique characterspublicclassStringUniqueCharacters{publicstaticvoidmain(String[]args){System.out.printf("%-40s %2s %10s %8s %s %s%n","String","Length","All Unique","1st Diff","Hex","Positions");System.out.printf("%-40s %2s %10s %8s %s %s%n","------------------------","------","----------","--------","---","---------");for(Strings:newString[]{"",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"}){processString(s);}}privatestaticvoidprocessString(Stringinput){Map<Character,Integer>charMap=newHashMap<>();chardup=0;intindex=0;intpos1=-1;intpos2=-1;for(charkey:input.toCharArray()){index++;if(charMap.containsKey(key)){dup=key;pos1=charMap.get(key);pos2=index;break;}charMap.put(key,index);}Stringunique=dup==0?"yes":"no";Stringdiff=dup==0?"":"'"+dup+"'";Stringhex=dup==0?"":Integer.toHexString(dup).toUpperCase();Stringposition=dup==0?"":pos1+" "+pos2;System.out.printf("%-40s %-6d %-10s %-8s %-3s %-5s%n",input,input.length(),unique,diff,hex,position);}}
String Length All Unique 1st Diff Hex Positions------------------------ ------ ---------- -------- --- --------- 0 yes . 1 yes abcABC 6 yes XYZ ZYX 7 no 'Z' 5A 3 5 1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ 36 no '0' 30 10 25
importjava.util.HashSet;importjava.util.List;importjava.util.OptionalInt;importjava.util.Set;publicfinalclassDetermineUniqueCharacters{publicstaticvoidmain(String[]aArgs){List<String>words=List.of("",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ");for(Stringword:words){Set<Integer>seen=newHashSet<Integer>();OptionalIntfirst=word.chars().filter(ch->!seen.add(ch)).findFirst();if(first.isPresent()){finalcharch=(char)first.getAsInt();finalStringhex=Integer.toHexString(ch).toUpperCase();System.out.println("Word: \""+word+"\" contains a repeated character.");System.out.println("Character '"+ch+"' (hex "+hex+") occurs at positions "+word.indexOf(ch)+" and "+word.indexOf(ch,word.indexOf(ch)+1));}else{System.out.println("Word: \""+word+"\" has all unique characters.");}System.out.println();}}}
Word: "" has all unique characters.Word: "." has all unique characters.Word: "abcABC" has all unique characters.Word: "XYZ ZYX" contains a repeated character.Character 'Z' (hex 5A) occurs at positions 2 and 4Word: "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" contains a repeated character.Character '0' (hex 30) occurs at positions 9 and 24
(()=>{'use strict';// duplicatedCharIndices :: String -> Maybe (Char, [Int])constduplicatedCharIndices=s=>{constduplicates=filter(g=>1<g.length)(groupBy(on(eq)(snd))(sortOn(snd)(zip(enumFrom(0))(chars(s)))));return0<duplicates.length?Just(fanArrow(compose(snd,fst))(map(fst))(sortOn(compose(fst,fst))(duplicates)[0])):Nothing();};// ------------------------TEST------------------------constmain=()=>console.log(fTable('First duplicated character, if any:')(s=>`'${s}' (${s.length})`)(maybe('None')(tpl=>{const[c,ixs]=Array.from(tpl);return`'${c}' (0x${showHex(ord(c))}) at${ixs.join(', ')}`}))(duplicatedCharIndices)(["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"]));// -----------------GENERIC FUNCTIONS------------------// Just :: a -> Maybe aconstJust=x=>({type:'Maybe',Nothing:false,Just:x});// Nothing :: Maybe aconstNothing=()=>({type:'Maybe',Nothing:true,});// Tuple (,) :: a -> b -> (a, b)constTuple=a=>b=>({type:'Tuple','0':a,'1':b,length:2});// chars :: String -> [Char]constchars=s=>s.split('');// compose (<<<) :: (b -> c) -> (a -> b) -> a -> cconstcompose=(...fs)=>x=>fs.reduceRight((a,f)=>f(a),x);// enumFrom :: Enum a => a -> [a]function*enumFrom(x){letv=x;while(true){yieldv;v=1+v;}}// eq (==) :: Eq a => a -> a -> Boolconsteq=a=>b=>a===b;// fanArrow (&&&) :: (a -> b) -> (a -> c) -> (a -> (b, c))constfanArrow=f=>// Compose a function from a simple value to a tuple of// the separate outputs of two different functions.g=>x=>Tuple(f(x))(g(x));// filter :: (a -> Bool) -> [a] -> [a]constfilter=f=>xs=>xs.filter(f);// fst :: (a, b) -> aconstfst=tpl=>tpl[0];// fTable :: String -> (a -> String) -> (b -> String)// -> (a -> b) -> [a] -> StringconstfTable=s=>xShow=>fxShow=>f=>xs=>{// Heading -> x display function ->// fx display function ->// f -> values -> tabular stringconstys=xs.map(xShow),w=Math.max(...ys.map(length));returns+'\n'+zipWith(a=>b=>a.padStart(w,' ')+' -> '+b)(ys)(xs.map(x=>fxShow(f(x)))).join('\n');};// groupBy :: (a -> a -> Bool) -> [a] -> [[a]]constgroupBy=fEq=>// Typical usage: groupBy(on(eq)(f), xs)xs=>0<xs.length?(()=>{consttpl=xs.slice(1).reduce((gw,x)=>{constgps=gw[0],wkg=gw[1];returnfEq(wkg[0])(x)?(Tuple(gps)(wkg.concat([x]))):Tuple(gps.concat([wkg]))([x]);},Tuple([])([xs[0]]));returntpl[0].concat([tpl[1]])})():[];// length :: [a] -> Intconstlength=xs=>// Returns Infinity over objects without finite length.// This enables zip and zipWith to choose the shorter// argument when one is non-finite, like cycle, repeat etc(Array.isArray(xs)||'string'===typeofxs)?(xs.length):Infinity;// map :: (a -> b) -> [a] -> [b]constmap=f=>xs=>(Array.isArray(xs)?(xs):xs.split('')).map(f);// maybe :: b -> (a -> b) -> Maybe a -> bconstmaybe=v=>// Default value (v) if m is Nothing, or f(m.Just)f=>m=>m.Nothing?v:f(m.Just);// on :: (b -> b -> c) -> (a -> b) -> a -> a -> cconston=f=>g=>a=>b=>f(g(a))(g(b));// ord :: Char -> Intconstord=c=>c.codePointAt(0);// showHex :: Int -> StringconstshowHex=n=>n.toString(16);// snd :: (a, b) -> bconstsnd=tpl=>tpl[1];// sortOn :: Ord b => (a -> b) -> [a] -> [a]constsortOn=f=>// Equivalent to sortBy(comparing(f)), but with f(x)// evaluated only once for each x in xs.// ('Schwartzian' decorate-sort-undecorate).xs=>xs.map(x=>[f(x),x]).sort((a,b)=>a[0]<b[0]?-1:(a[0]>b[0]?1:0)).map(x=>x[1]);// take :: Int -> [a] -> [a]// take :: Int -> String -> Stringconsttake=n=>xs=>'GeneratorFunction'!==xs.constructor.constructor.name?(xs.slice(0,n)):[].concat.apply([],Array.from({length:n},()=>{constx=xs.next();returnx.done?[]:[x.value];}));// uncurry :: (a -> b -> c) -> ((a, b) -> c)constuncurry=f=>(x,y)=>f(x)(y)// zip :: [a] -> [b] -> [(a, b)]constzip=xs=>ys=>{constlng=Math.min(length(xs),length(ys)),vs=take(lng)(ys);returntake(lng)(xs).map((x,i)=>Tuple(x)(vs[i]));};// zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]constzipWith=f=>xs=>ys=>{constlng=Math.min(length(xs),length(ys)),vs=take(lng)(ys);returntake(lng)(xs).map((x,i)=>f(x)(vs[i]));};// MAIN ---returnmain();})();
First duplicated character, if any: '' (0) -> None '.' (1) -> None 'abcABC' (6) -> None 'XYZ ZYX' (7) -> 'X' (0x58) at 0, 6'1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ' (36) -> '0' (0x30) at 9, 24
Or, as an alternative to sorting and grouping – folding a string down to a dictionary of indices:
(()=>{'use strict';// duplicatedCharIndices :: String -> Maybe (Char, [Int])constduplicatedCharIndices=s=>minimumByMay(comparing(compose(fst,snd)))(filter(x=>1<x[1].length)(Object.entries(s.split('').reduce((a,c,i)=>Object.assign(a,{[c]:(a[c]||[]).concat(i)}),{}))));// ------------------------TEST------------------------constmain=()=>console.log(fTable('First duplicated character, if any:')(s=>`'${s}' (${s.length})`)(maybe('None')(tpl=>{const[c,ixs]=Array.from(tpl);return`'${c}' (0x${showHex(ord(c))}) at${ixs.join(', ')}`}))(duplicatedCharIndices)(["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"]));// -----------------GENERIC FUNCTIONS------------------// Just :: a -> Maybe aconstJust=x=>({type:'Maybe',Nothing:false,Just:x});// Nothing :: Maybe aconstNothing=()=>({type:'Maybe',Nothing:true,});// Tuple (,) :: a -> b -> (a, b)constTuple=a=>b=>({type:'Tuple','0':a,'1':b,length:2});// chars :: String -> [Char]constchars=s=>s.split('');// comparing :: (a -> b) -> (a -> a -> Ordering)constcomparing=f=>x=>y=>{consta=f(x),b=f(y);returna<b?-1:(a>b?1:0);};// compose (<<<) :: (b -> c) -> (a -> b) -> a -> cconstcompose=(...fs)=>x=>fs.reduceRight((a,f)=>f(a),x);// enumFrom :: Enum a => a -> [a]function*enumFrom(x){letv=x;while(true){yieldv;v=1+v;}}// filter :: (a -> Bool) -> [a] -> [a]constfilter=f=>xs=>xs.filter(f);// fst :: (a, b) -> aconstfst=tpl=>tpl[0];// fTable :: String -> (a -> String) -> (b -> String)// -> (a -> b) -> [a] -> StringconstfTable=s=>xShow=>fxShow=>f=>xs=>{// Heading -> x display function ->// fx display function ->// f -> values -> tabular stringconstys=xs.map(xShow),w=Math.max(...ys.map(length));returns+'\n'+zipWith(a=>b=>a.padStart(w,' ')+' -> '+b)(ys)(xs.map(x=>fxShow(f(x)))).join('\n');};// length :: [a] -> Intconstlength=xs=>// Returns Infinity over objects without finite length.// This enables zip and zipWith to choose the shorter// argument when one is non-finite, like cycle, repeat etc(Array.isArray(xs)||'string'===typeofxs)?(xs.length):Infinity;// maybe :: b -> (a -> b) -> Maybe a -> bconstmaybe=v=>// Default value (v) if m is Nothing, or f(m.Just)f=>m=>m.Nothing?v:f(m.Just);// minimumByMay :: (a -> a -> Ordering) -> [a] -> Maybe aconstminimumByMay=f=>xs=>xs.reduce((a,x)=>a.Nothing?Just(x):(f(x)(a.Just)<0?Just(x):a),Nothing());// ord :: Char -> Intconstord=c=>c.codePointAt(0);// showHex :: Int -> StringconstshowHex=n=>n.toString(16);// snd :: (a, b) -> bconstsnd=tpl=>tpl[1];// take :: Int -> [a] -> [a]// take :: Int -> String -> Stringconsttake=n=>xs=>'GeneratorFunction'!==xs.constructor.constructor.name?(xs.slice(0,n)):[].concat.apply([],Array.from({length:n},()=>{constx=xs.next();returnx.done?[]:[x.value];}));// zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]constzipWith=f=>xs=>ys=>{constlng=Math.min(length(xs),length(ys)),vs=take(lng)(ys);returntake(lng)(xs).map((x,i)=>f(x)(vs[i]));};// MAIN ---returnmain();})();
First duplicated character, if any: '' (0) -> None '.' (1) -> None 'abcABC' (6) -> None 'XYZ ZYX' (7) -> 'X' (0x58) at 0, 6'1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ' (36) -> '0' (0x30) at 9, 24
"First Duplicate" is here understood to be the first character found to be a duplicatewhen scanning from left to right, so the First Duplicate in XYYX is Y. It would require only a trivialmodification of `firstDuplicate` as defined here to implement the alternativeinterpretation as the first character to be duplicated.
# Emit null if there is no duplicate, else [c, [ix1, ix2]]def firstDuplicate: label $out | foreach explode[] as $i ({ix: -1}; .ix += 1 | .ix as $ix | .iu = ([$i] | implode) | .[.iu] += [ $ix] ; if .[.iu]|length == 2 then [.iu, .[.iu]], break $out else empty end ) // null ;
Some helper functions for accomplishing other aspects of the task:
# hex of a number or a single (unicode) characterdef hex: def stream: recurse(if . >= 16 then ./16|floor else empty end) | . % 16 ; if type=="string" then explode[0] else . end | [stream] | reverse | map(if . < 10 then 48 + . else . + 87 end) | implode ;def lpad($len): tostring | " " * ($len - width) + .;def q: "«\(.)»";def header: "\("string"|q|lpad(38)) : |s| : C : hex IO=0";def data: "", ".", "abcABC", "XYZ ZYX", "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ", "😍😀🙌💃😍🙌" ;
The main program:
header, (data | firstDuplicate as [$k, $v] | "\(q|lpad(38)) : \(length|lpad(4)) : \($k // " ") : \($k |if . then hex else " " end) \($v // [])" )
«string»:|s|:C:hexIO=0«»:0::[]«.»:1::[]«abcABC»:6::[]«XYZZYX»:7:Z:5A[2,4]«1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ»:36:0:30[9,24]«😍😀🙌💃😍🙌»:6:😍:1f60d[0,4]
The last line above was adjusted manually as jq has no built-in function for computing the horizontal "printing" width of unicode strings in general.
arr(s)=[cforcins]alldup(a)=filter(x->length(x)>1,[findall(x->x==a[i],a)foriin1:length(a)])firstduplicate(s)=(a=arr(s);d=alldup(a);isempty(d)?nothing:first(d))functiontestfunction(strings)println("String | Length | All Unique | First Duplicate | Positions\n"*"-------------------------------------------------------------------------------------")forsinstringsn=firstduplicate(s)a=arr(s)println(rpad(s,38),rpad(length(s),11),n==nothing?"yes":rpad("no$(a[n[1]])",26)*rpad(n[1],4)*"$(n[2])")endendtestfunction(["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ","hétérogénéité","🎆🎃🎇🎈","😍😀🙌💃😍🙌","🐠🐟🐡🦈🐬🐳🐋🐡",])
String | Length | All Unique | First Duplicate (Hex) | Positions------------------------------------------------------------------------------------------- 0 yes. 1 yesabcABC 6 yesXYZ ZYX 7 no X (58) 1 71234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ 36 no 0 (30) 10 25hétérogénéité 13 no é (e9) 2 4🎆🎃🎇🎈 4 yes😍😀🙌💃😍🙌 6 no 😍 (1f60d) 1 5🐠🐟🐡🦈🐬🐳🐋🐡 8 no 🐡 (1f421) 3 8
importjava.util.HashMapfunmain(){System.out.printf("%-40s %2s %10s %8s %s %s%n","String","Length","All Unique","1st Diff","Hex","Positions")System.out.printf("%-40s %2s %10s %8s %s %s%n","------------------------","------","----------","--------","---","---------")for(sinarrayOf("",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ")){processString(s)}}privatefunprocessString(input:String){valcharMap:MutableMap<Char,Int?>=HashMap()vardup=0.toChar()varindex=0varpos1=-1varpos2=-1for(keyininput.toCharArray()){index++if(charMap.containsKey(key)){dup=keypos1=charMap[key]!!pos2=indexbreak}charMap[key]=index}valunique=if(dup.toInt()==0)"yes"else"no"valdiff=if(dup.toInt()==0)""else"'$dup'"valhex=if(dup.toInt()==0)""elseInteger.toHexString(dup.toInt()).toUpperCase()valposition=if(dup.toInt()==0)""else"$pos1 $pos2"System.out.printf("%-40s %-6d %-10s %-8s %-3s %-5s%n",input,input.length,unique,diff,hex,position)}
String Length All Unique 1st Diff Hex Positions------------------------ ------ ---------- -------- --- --------- 0 yes . 1 yes abcABC 6 yes XYZ ZYX 7 no 'Z' 5A 3 5 1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ 36 no '0' 30 10 25
Using regular expressions. The '-' in the pattern's '.-' is the "lazy" or "reluctant" repetition qualifier; the usual '.*'would caused pattern to match, in the first example below, the substring "cocc" instead of "coc".
localfind,format=string.find,string.formatlocalfunctionprintf(fmt,...)print(format(fmt,...))endlocalpattern='(.).-%1'-- '(.)' .. '.-' .. '%1'functionreport_dup_char(subject)localpos1,pos2,char=find(subject,pattern)localprefix=format('"%s" (%d)',subject,#subject)ifpos1thenlocalbyte=char:byte()printf("%s: '%s' (0x%02x) duplicates at %d, %d",prefix,char,byte,pos1,pos2)elseprintf("%s: no duplicates",prefix)endendlocalshow=report_dup_charshow('coccyx')show('')show('.')show('abcABC')show('XYZ ZYX')show('1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ')
"coccyx" (6): 'c' (0x63) duplicates at 1, 3"" (0): no duplicates"." (1): no duplicates"abcABC" (6): no duplicates"XYZ ZYX" (7): 'X' (0x58) duplicates at 1, 7"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (36): '0' (0x30) duplicates at 10, 25
modulefind_unique{form88,40flushdata"",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"res0="{0:36}|{1:-6}|"res1="all characters are unique"res2="1st duplicate character 0x{0} at {1:-2} and {2:-2}"open"output.txt"forwideoutputas#fPrint#f,format$(res0,"String","Length");"Test"whilenotemptycheck()endwhileclose#fwin"output.txt"subcheck(word$)print#f,format$(res0,word$,len(word$));iflen(word$)>0thenLocali,k=list,c$fori=1tolen(word$)c$=mid$(word$,i,1)ifnotexist(k,c$)thenappendk,c$elsePrint#f,format$(res2,hex$(chrcode(c$),2),eval(k!)+1,i)exitsubendifnextendifPrint#f,res1endsub}find_unique
String |Length|Test | 0|all characters are unique. | 1|all characters are uniqueabcABC | 6|all characters are uniqueXYZ ZYX | 7|1st duplicate character 0x005A at 3 and 51234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ| 36|1st duplicate character 0x0030 at 10 and 25
CheckUnique:=proc(s)local i, index;printf("input: \"%s\", length: %a\n", s, StringTools:-Length(s));for i from 1 to StringTools:-Length(s) doindex := StringTools:-SearchAll(s[i], s);if (numelems([index]) > 1) thenprintf("The given string has duplicated characters.\n");printf("The first duplicated character is %a (0x%x) which appears at index %a.\n\n", s[i], convert(s[i], 'bytes')[1], {index});return;end if;end do;# if no repeated foundprintf("The given string has all unique characters.\n\n");end proc:# TestCheckUnique("");CheckUnique(".");CheckUnique("abcABC");CheckUnique("XYZ ZYX");CheckUnique("1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ");
input: "", length: 0The given string has all unique characters.input: ".", length: 1The given string has all unique characters.input: "abcABC", length: 6The given string has all unique characters.input: "XYZ ZYX", length: 7The given string has duplicated characters.The first duplicated character is "X" (0x58) which appears at index {1, 7}.input: "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ", length: 36The given string has duplicated characters.The first duplicated character is "0" (0x30) which appears at index {10, 25}.
ClearAll[UniqueCharacters]UniqueCharacters[s_String]:=Module[{c,len,good=True},c=Characters[s];len=Length[c];Print[s," with length ",len];Do[If[c[[i]]==c[[j]],Print["Character ",c[[i]]," is repeated at positions ",i," and ",j];good=False],{i,len-1},{j,i+1,len}];If[good,Print["No repeats"];True,False]]UniqueCharacters[""]UniqueCharacters["."]UniqueCharacters["abcABC"]UniqueCharacters["XYZ ZYX"]UniqueCharacters["1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"]
with length 0No repeatsTrue. with length 1No repeatsTrueabcABC with length 6No repeatsTrueXYZ ZYX with length 7Character X is repeated at positions 1 and 7Character Y is repeated at positions 2 and 6Character Z is repeated at positions 3 and 5False1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ with length 36Character 0 is repeated at positions 10 and 25False
def analyze(s) s = str(s) println "Examining [" + s + "] which has a length of " + str(len(s)) + ":" if len(s) < 2 println "\tAll characters in the string are unique." return end seen = list() for i in range(0, len(s) - 2) if s[i] in seen println "\tNot all characters in the string are unique." println "\t'" + s[i] + "' " + format("(0x%x)", ord(s[i])) +\ " is duplicated at positions " + str(i + 1) + " and " +\ str(s.indexOf(s[i]) + 1) return end seen.append(s[i]) end println "\tAll characters in the string are unique."endtests = {"", ".", "abcABC", "XYZ ZYX", "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"}for s in tests analyze(s)end
Examining [] which has a length of 0: All characters in the string are unique.Examining [.] which has a length of 1: All characters in the string are unique.Examining [abcABC] which has a length of 6: All characters in the string are unique.Examining [XYZ ZYX] which has a length of 7: Not all characters in the string are unique. 'Z' (0x5a) is duplicated at positions 5 and 3Examining [1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ] which has a length of 36: Not all characters in the string are unique. '0' (0x30) is duplicated at positions 25 and 10
importunicode,strformatproccheckUniqueChars(s:string)=echofmt"Checking string""{s}"":"letrunes=s.toRunesforiin0..<runes.high:letrune=runes[i]forjin(i+1)..runes.high:ifrunes[j]==rune:echo"The string contains duplicate characters."echofmt"Character {rune} ({int(rune):x}) is present at positions {i+1} and {j+1}."echo""returnecho"All characters in the string are unique."echo""constStrings=["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ","hétérogénéité","🎆🎃🎇🎈","😍😀🙌💃😍🙌","🐠🐟🐡🦈🐬🐳🐋🐡"]forsinStrings:s.checkUniqueChars()
Checking string "":All characters in the string are unique.Checking string ".":All characters in the string are unique.Checking string "abcABC":All characters in the string are unique.Checking string "XYZ ZYX":The string contains duplicate characters.Character X (58) is present at positions 1 and 7.Checking string "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ":The string contains duplicate characters.Character 0 (30) is present at positions 10 and 25.Checking string "hétérogénéité":The string contains duplicate characters.Character é (e9) is present at positions 2 and 4.Checking string "🎆🎃🎇🎈":All characters in the string are unique.Checking string "😍😀🙌💃😍🙌":The string contains duplicate characters.Character 😍 (1f60d) is present at positions 1 and 5.Checking string "🐠🐟🐡🦈🐬🐳🐋🐡":The string contains duplicate characters.Character 🐡 (1f421) is present at positions 3 and 8.
Using a map to store characters we've met (as keys) and their first position (as indexes).
moduleCMap=Map.Make(structtypet=charletcompare=compareend)(** Add index as argument to string.fold_left *)letstring_fold_left_ifaccstr=snd(String.fold_left(fun(index,acc)char->(index+1,faccindexchar))(0,acc)str)exceptionFoundofint*int*charlethas_duplicatesstr=trylet_=string_fold_left_i(funmapindexchar->matchCMap.find_optcharmapwith|None->CMap.addcharindexmap|Somei->raise(Found(i,index,char)))CMap.emptystrinOk()withFound(i,j,c)->Error(i,j,c)letprinterstr=Format.printf"%S (len %d) : "str(String.lengthstr);matchhas_duplicatesstrwith|Ok()->Format.printf"No duplicates.\n"|Error(i,j,c)->Format.printf"Duplicate '%c' (%#x) at %d and %d\n"c(int_of_charc)ijlet()=printer"";printer".";printer"abcABC";printer"XYZ ZYX";printer"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"
"" (len 0) : No duplicates."." (len 1) : No duplicates."abcABC" (len 6) : No duplicates."XYZ ZYX" (len 7) : Duplicate 'Z' (0x5a) at 2 and 4"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (len 36) : Duplicate '0' (0x30) at 9 and 24
##varinput:=|'','.','abcABC','XYZ ZYX','1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ'|;foreachvarsininputdoWriteln('''',s,'''',' (Length ',s.Length,') ',String.Join(', ',s.Select((c,i)->(c,i)).GroupBy(t->t[0]).Where(g->g.Count()>1).Select(g->''''+g.Key+'''(0X'+Ord(g.key).ToString('x')+') ['+String.Join(', ',g.Select(t->t[1]))+']').DefaultIfEmpty('All characters are unique.')));
'' (Length 0) All characters are unique.'.' (Length 1) All characters are unique.'abcABC' (Length 6) All characters are unique.'XYZ ZYX' (Length 7) 'X'(0X58) [0, 6], 'Y'(0X59) [1, 5], 'Z'(0X5a) [2, 4]'1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ' (Length 36) '0'(0X30) [9, 24]
usestrict;usewarnings;usefeature'say';useutf8;binmode(STDOUT,':utf8');useList::AllUtilsqw(uniq);useUnicode::UCD'charinfo';formy$str('','.','abcABC','XYZ ZYX','1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ','01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X','Δ👍👨👍Δ','ΔδΔ̂ΔΛ',){my@S;push@S,$1while$str=~ /(\X)/g;printfqq{\n"$str" (length: %d) has },scalar@S;if(@S!=uniq@S){say"duplicated characters:";my%P;push@{$P{$S[$_]}},1+$_for0..$#S;formy$k(sortkeys%P){nextunless@{$P{$k}}>1;printf"'%s' %s (0x%x) in positions: %s\n",$k,charinfo(ord$k)->{'name'},ord($k),join', ',@{$P{$k}};}}else{say"no duplicated characters."}}
"" (length: 0) has no duplicated characters."." (length: 1) has no duplicated characters."abcABC" (length: 6) has no duplicated characters."XYZ ZYX" (length: 7) has duplicated characters:'X' LATIN CAPITAL LETTER X (0x58) in positions: 1, 7'Y' LATIN CAPITAL LETTER Y (0x59) in positions: 2, 6'Z' LATIN CAPITAL LETTER Z (0x5a) in positions: 3, 5"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (length: 36) has duplicated characters:'0' DIGIT ZERO (0x30) in positions: 10, 25"01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X" (length: 39) has duplicated characters:'0' DIGIT ZERO (0x30) in positions: 1, 11, 26, 38'X' LATIN CAPITAL LETTER X (0x58) in positions: 35, 39"Δ👍👨👍Δ" (length: 5) has duplicated characters:'Δ' GREEK CAPITAL LETTER DELTA (0x394) in positions: 1, 5'👍' THUMBS UP SIGN (0x1f44d) in positions: 2, 4"ΔδΔ̂ΔΛ" (length: 5) has duplicated characters:'Δ' GREEK CAPITAL LETTER DELTA (0x394) in positions: 1, 4
As withDetermine_if_a_string_has_all_the_same_characters#Phix, you can use utf8_to_utf32() when needed.
procedureall_uniq(sequences)stringchars=""sequenceposns={},multi={}integerlm=0fori=1tolength(s)dointegersi=s[i],k=find(si,chars)ifk=0thenchars&=siposns&={{i}}elseposns[k]&=iiflength(posns[k])=2thenmulti&=klm+=1endifendifendforstringmsg=sprintf("\"%s\" (length %d): ",{s,length(s)}),nod=ordinal(lm,true),ess="s"[1..lm>1],res=iff(lm=0?"all characters are unique":sprintf("contains %s duplicate%s:",{nod,ess}))printf(1,"%s %s\n",{msg,res})res=repeat(' ',length(msg))fori=1tolength(multi)dointegermi=multi[i],ci=chars[mi]printf(1,"%s '%c'(#%02x) at %V\n",{res,ci,ci,posns[mi]})endforprintf(1,"\n")endprocedureconstanttests={"",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ","01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X"," ","2","333","55","tttTTT","tTTTtt","4444 444k"}papply(tests,all_uniq)
"" (length 0): all characters are unique"." (length 1): all characters are unique"abcABC" (length 6): all characters are unique"XYZ ZYX" (length 7): contains three duplicates: 'Z'(#5A) at {3,5} 'Y'(#59) at {2,6} 'X'(#58) at {1,7}"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (length 36): contains one duplicate: '0'(#30) at {10,25}"01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X" (length 39): contains two duplicates: '0'(#30) at {1,11,26,38} 'X'(#58) at {35,39}" " (length 3): contains one duplicate: ' '(#20) at {1,2,3}"2" (length 1): all characters are unique"333" (length 3): contains one duplicate: '3'(#33) at {1,2,3}"55" (length 2): contains one duplicate: '5'(#35) at {1,2}"tttTTT" (length 6): contains two duplicates: 't'(#74) at {1,2,3} 'T'(#54) at {4,5,6}"tTTTtt" (length 6): contains two duplicates: 'T'(#54) at {2,3,4} 't'(#74) at {1,5,6}"4444 444k" (length 9): contains one duplicate: '4'(#34) at {1,2,3,4,6,7,8}
The results are effectively printed in order of posns[2], but that can easily be changed, for example by sorting multi before that final print loop.
(de burn (Lst) (let P 0 (by '((A) (set A (inc 'P)) (put A 'P (char A)) ) group Lst ) ) )(de first (Lst) (mini '((L) (nand (cdr L) (apply min (mapcar val L)) ) ) Lst ) )(de uniq? (Str) (let M (first (burn (chop Str))) (ifn M (prinl Str " (length " (length Str) "): all characters are unique") (prin Str " (length " (length Str) "): first duplicate character " (car M) " at positions " ) (println (mapcar val M)) ) ) )(uniq?)(uniq? ".")(uniq? "abcABC")(uniq? "XYZ ZYX")(uniq? "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ")
(length 0): all characters are unique. (length 1): all characters are uniqueabcABC (length 6): all characters are uniqueXYZ ZYX (length 7): first duplicate character X at positions (1 7)1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ (length 36): first duplicate character 0 at positions (10 25)
report_duplicates(S):-duplicates(S,Dups),format('For value "~w":~n',S),report(Dups),nl.report(Dups):-maplist(only_one_position,Dups),format(' All characters are unique~n').report(Dups):-exclude(only_one_position,Dups,[c(Char,Positions)|_]),reverse(Positions,PosInOrder),atomic_list_concat(PosInOrder,', ',PosAsList),format(' The character ~w is non unique at ~p~n',[Char,PosAsList]).only_one_position(c(_,[_])).duplicates(S,Count):-atom_chars(S,Chars),char_count(Chars,0,[],Count).char_count([],_,C,C).char_count([C|T],Index,Counted,Result):-select(c(C,Positions),Counted,MoreCounted),succ(Index,Index1),char_count(T,Index1,[c(C,[Index|Positions])|MoreCounted],Result).char_count([C|T],Index,Counted,Result):-\+member(c(C,_),Counted),succ(Index,Index1),char_count(T,Index1,[c(C,[Index])|Counted],Result).test:-report_duplicates('').test:-report_duplicates('.').test:-report_duplicates('abcABC').test:-report_duplicates('XYZ ZYX').test:-report_duplicates('1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ').
?- forall(test, true).For value "": All characters are uniqueFor value ".": All characters are uniqueFor value "abcABC": All characters are uniqueFor value "XYZ ZYX": The character X is non unique at '0, 6'For value "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ": The character 0 is non unique at '9, 24'true.?-
Defined in terms of itertools.groupby:
'''Determine if a string has all unique characters'''fromitertoolsimportgroupby# duplicatedCharIndices :: String -> Maybe (Char, [Int])defduplicatedCharIndices(s):'''Just the first duplicated character, and the indices of its occurrence, or Nothing if there are no duplications. '''defgo(xs):if1<len(xs):duplicates=list(filter(lambdakv:1<len(kv[1]),[(k,list(v))fork,vingroupby(sorted(xs,key=swap),key=snd)]))returnJust(second(fmap(fst))(sorted(duplicates,key=lambdakv:kv[1][0])[0]))ifduplicateselseNothing()else:returnNothing()returngo(list(enumerate(s)))# TEST ----------------------------------------------------# main :: IO ()defmain():'''Test over various strings.'''defshowSample(s):returnrepr(s)+' ('+str(len(s))+')'defshowDuplicate(cix):c,ix=cixreturnrepr(c)+(' ('+hex(ord(c))+') at '+repr(ix))print(fTable('First duplicated character, if any:')(showSample)(maybe('None')(showDuplicate))(duplicatedCharIndices)(['','.','abcABC','XYZ ZYX','1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ']))# FORMATTING ----------------------------------------------# fTable :: String -> (a -> String) -># (b -> String) -> (a -> b) -> [a] -> StringdeffTable(s):'''Heading -> x display function -> fx display function -> f -> xs -> tabular string. '''defgo(xShow,fxShow,f,xs):ys=[xShow(x)forxinxs]w=max(map(len,ys))returns+'\n'+'\n'.join(map(lambdax,y:y.rjust(w,' ')+' -> '+fxShow(f(x)),xs,ys))returnlambdaxShow:lambdafxShow:lambdaf:lambdaxs:go(xShow,fxShow,f,xs)# GENERIC -------------------------------------------------# Just :: a -> Maybe adefJust(x):'''Constructor for an inhabited Maybe (option type) value. Wrapper containing the result of a computation. '''return{'type':'Maybe','Nothing':False,'Just':x}# Nothing :: Maybe adefNothing():'''Constructor for an empty Maybe (option type) value. Empty wrapper returned where a computation is not possible. '''return{'type':'Maybe','Nothing':True}# fmap :: (a -> b) -> [a] -> [b]deffmap(f):'''fmap over a list. f lifted to a function over a list. '''returnlambdaxs:[f(x)forxinxs]# fst :: (a, b) -> adeffst(tpl):'''First member of a pair.'''returntpl[0]# head :: [a] -> adefhead(xs):'''The first element of a non-empty list.'''returnxs[0]ifisinstance(xs,list)elsenext(xs)# maybe :: b -> (a -> b) -> Maybe a -> bdefmaybe(v):'''Either the default value v, if m is Nothing, or the application of f to x, where m is Just(x). '''returnlambdaf:lambdam:vif(Noneismorm.get('Nothing'))elsef(m.get('Just'))# second :: (a -> b) -> ((c, a) -> (c, b))defsecond(f):'''A simple function lifted to a function over a tuple, with f applied only to the second of two values. '''returnlambdaxy:(xy[0],f(xy[1]))# snd :: (a, b) -> bdefsnd(tpl):'''Second member of a pair.'''returntpl[1]# swap :: (a, b) -> (b, a)defswap(tpl):'''The swapped components of a pair.'''return(tpl[1],tpl[0])# MAIN ---if__name__=='__main__':main()
First duplicated character, if any: '' (0) -> None '.' (1) -> None 'abcABC' (6) -> None 'XYZ ZYX' (7) -> 'X' (0x58) at [0, 6]'1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ' (36) -> '0' (0x30) at [9, 24]
Or, as an alternative to sorting and grouping, folding a string down to a dictionary withreduce:
'''Determine if a string has all unique characters'''fromfunctoolsimportreduce# duplicatedCharIndices :: String -> Maybe (Char, [Int])defduplicatedCharIndices(s):'''Just the first duplicated character, and the indices of its occurrence, or Nothing if there are no duplications. '''defgo(dct,ic):i,c=icreturndict(dct,**{c:dct[c]+[i]ifcindctelse[i]})duplicates=[(k,v)for(k,v)inreduce(go,enumerate(s),{}).items()if1<len(v)]returnJust(min(duplicates,key=compose(head,snd)))ifduplicateselseNothing()# And another alternative here would be to fuse the 1 < len(v)# filtering, and the min() search for the earliest duplicate,# down to a single `earliestDuplication` fold:# duplicatedCharIndices_ :: String -> Maybe (Char, [Int])defduplicatedCharIndices_(s):'''Just the first duplicated character, and the indices of its occurrence, or Nothing if there are no duplications. '''defpositionRecord(dct,ic):i,c=icreturndict(dct,**{c:dct[c]+[i]ifcindctelse[i]})defearliestDuplication(sofar,charPosns):c,indices=charPosnsreturn(maybe(Just((c,indices)))(lambdakxs:Just((c,indices))if(# Earlier duplication ?indices[0]<kxs[1][0])elsesofar)(sofar))if1<len(indices)elsesofarreturnreduce(earliestDuplication,reduce(positionRecord,enumerate(s),{}).items(),Nothing())# TEST ----------------------------------------------------# main :: IO ()defmain():'''Test over various strings.'''defshowSample(s):returnrepr(s)+' ('+str(len(s))+')'defshowDuplicate(cix):c,ix=cixreturnrepr(c)+(' ('+hex(ord(c))+') at '+repr(ix))print(fTable('First duplicated character, if any:')(showSample)(maybe('None')(showDuplicate))(duplicatedCharIndices_)(['','.','abcABC','XYZ ZYX','1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ']))# FORMATTING ----------------------------------------------# fTable :: String -> (a -> String) -># (b -> String) -> (a -> b) -> [a] -> StringdeffTable(s):'''Heading -> x display function -> fx display function -> f -> xs -> tabular string. '''defgo(xShow,fxShow,f,xs):ys=[xShow(x)forxinxs]w=max(map(len,ys))returns+'\n'+'\n'.join(map(lambdax,y:y.rjust(w,' ')+' -> '+fxShow(f(x)),xs,ys))returnlambdaxShow:lambdafxShow:lambdaf:lambdaxs:go(xShow,fxShow,f,xs)# GENERIC -------------------------------------------------# Just :: a -> Maybe adefJust(x):'''Constructor for an inhabited Maybe (option type) value. Wrapper containing the result of a computation. '''return{'type':'Maybe','Nothing':False,'Just':x}# Nothing :: Maybe adefNothing():'''Constructor for an empty Maybe (option type) value. Empty wrapper returned where a computation is not possible. '''return{'type':'Maybe','Nothing':True}# compose :: ((a -> a), ...) -> (a -> a)defcompose(*fs):'''Composition, from right to left, of a series of functions. '''returnlambdax:reduce(lambdaa,f:f(a),fs[::-1],x)# head :: [a] -> adefhead(xs):'''The first element of a non-empty list.'''returnxs[0]ifisinstance(xs,list)elsenext(xs)# maybe :: b -> (a -> b) -> Maybe a -> bdefmaybe(v):'''Either the default value v, if m is Nothing, or the application of f to x, where m is Just(x). '''returnlambdaf:lambdam:vif(Noneismorm.get('Nothing'))elsef(m.get('Just'))# snd :: (a, b) -> bdefsnd(tpl):'''Second member of a pair.'''returntpl[1]# MAIN ---if__name__=='__main__':main()
First duplicated character, if any: '' (0) -> None '.' (1) -> None 'abcABC' (6) -> None 'XYZ ZYX' (7) -> 'X' (0x58) at [0, 6]'1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ' (36) -> '0' (0x30) at [9, 24]
The second part of the pattern uses the '*?' match qualifier, which makes the match "lazy" or "reluctant". '.*' instead of '.*?'would have matched the substring "cocc" instead of "coc" in the first example below.Tested with Python 3.7.
importrepattern='(.)'+'.*?'+r'\1'deffind_dup_char(subject):match=re.search(pattern,subject)ifmatch:returnmatch.groups(0)[0],match.start(0),match.end(0)defreport_dup_char(subject):dup=find_dup_char(subject)prefix=f'"{subject}" ({len(subject)})'ifdup:ch,pos1,pos2=dupprint(f"{prefix}: '{ch}' (0x{ord(ch):02x}) duplicates at{pos1},{pos2-1}")else:print(f"{prefix}: no duplicate characters")show=report_dup_charshow('coccyx')show('')show('.')show('abcABC')show('XYZ ZYX')show('1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ')
"coccyx" (6): 'c' (0x63) duplicates at 0, 2"" (0): no duplicate characters"." (1): no duplicate characters"abcABC" (6): no duplicate characters"XYZ ZYX" (7): 'X' (0x58) duplicates at 0, 6"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (36): '0' (0x30) duplicates at 9, 24
[ over find swap found ] is has ( $ c --> b ) [ dip [ 0 0 true ] dup size 2 < iff drop done dup size 1 - times [ behead 2dup has iff [ swap find dip not 2swap 2drop i^ tuck + 1+ rot 0 conclude ] done drop ] drop ] is uniquechars ( $ --> n n b ) [ dup say 'String "' echo$ say '" has length ' dup size echo say ". " dup uniquechars iff [ say "There are no duplicated characters." drop 2drop ] else [ rot over peek dup say 'The character "' emit say '" (hex:' 16 base put echo base release say ") is at positions " swap echo say " and " echo say "." ] cr ] is task ( $ --> ) $ "" task $ "." task $ "abcABC" task $ "XYZ ZYX" task $ "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" task
String "" has length 0. There are no duplicated characters.String "." has length 1. There are no duplicated characters.String "abcABC" has length 6. There are no duplicated characters.String "XYZ ZYX" has length 7. The character "X" (hex:58) is at positions 0 and 6.String "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" has length 36. The character "0" (hex:30) is at positions 9 and 24.
Most of this is adapted fromDetermine if a string has all the same characters#R.
isAllUnique<-function(string){strLength<-nchar(string)if(length(strLength)>1){#R has a distinction between the length of a string and that of a character vector. It is a common source#of problems when coming from another language. We will try to avoid the topic here.#For our purposes, let us only say that there is a good reason why we have made#isAllUnique(c("foo", "bar") immediately throw an error.stop("This task is intended for character vectors with lengths of at most 1.")}elseif(length(strLength)==0){cat("Examining a character vector of length 0.","It is therefore made entirely of unique characters.\n")TRUE}elseif(strLength==0){cat("Examining a character vector of length 1, containing an empty string.","It is therefore made entirely of unique characters.\n")TRUE}elseif(strLength==1){cat("Examining the string",paste0(sQuote(string),","),"which is of length",paste0(strLength,"."),"It is therefore made entirely of unique characters.\n")TRUE}else{cat("Examining the string",paste0(sQuote(string),","),"which is of length",paste0(strLength,":"),"\n")#strsplit outputs a list. Its first element is the vector of characters that we desire.characters<-strsplit(string,"")[[1]]#Our use of match is using R's vector recycling rules. Element i is being checked#against every other.indexesOfDuplicates<-sapply(seq_len(strLength),function(i)match(TRUE,characters[i]==characters[-i],nomatch=-1))+1firstDuplicateElementIndex<-indexesOfDuplicates[indexesOfDuplicates!=0][1]if(is.na(firstDuplicateElementIndex)){cat("It has no duplicates. It is therefore made entirely of unique characters.\n")TRUE}else{cat("It has duplicates. ")firstDuplicatedCharacter<-characters[firstDuplicateElementIndex]cat(sQuote(firstDuplicatedCharacter),"is the first duplicated character. It has hex value",sprintf("0x%X",as.integer(charToRaw(firstDuplicatedCharacter))),"and is at index",paste0(firstDuplicateElementIndex,"."),"\nThis is a duplicate of the character at index",paste0(match(firstDuplicateElementIndex,indexesOfDuplicates),"."),"\n")FALSE}}}#Tests:cat("Test: A string of length 0 (an empty string):\n")cat("Test 1 of 2: An empty character vector:\n")print(isAllUnique(character(0)))cat("Test 2 of 2: A character vector containing the empty string:\n")print(isAllUnique(""))cat("Test: A string of length 1 which contains .:\n")print(isAllUnique("."))cat("Test: A string of length 6 which contains abcABC:\n")print(isAllUnique("abcABC"))cat("Test: A string of length 7 which contains XYZ ZYX:\n")print(isAllUnique("XYZ ZYX"))cat("Test: A string of length 36 doesn't contain the letter 'oh':\n")print(isAllUnique("1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"))
Test: A string of length 0 (an empty string):Test 1 of 2: An empty character vector:Examining a character vector of length 0. It is therefore made entirely of unique characters.[1] TRUETest 2 of 2: A character vector containing the empty string:Examining a character vector of length 1, containing an empty string. It is therefore made entirely of unique characters.[1] TRUETest: A string of length 1 which contains .:Examining the string ‘.’, which is of length 1. It is therefore made entirely of unique characters.[1] TRUETest: A string of length 6 which contains abcABC:Examining the string ‘abcABC’, which is of length 6: It has no duplicates. It is therefore made entirely of unique characters.[1] TRUETest: A string of length 7 which contains XYZ ZYX:Examining the string ‘XYZ ZYX’, which is of length 7: It has duplicates. ‘X’ is the first duplicated character. It has hex value 0x58 and is at index 7. This is a duplicate of the character at index 1. [1] FALSETest: A string of length 36 doesn't contain the letter 'oh':Examining the string ‘1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ’, which is of length 36: It has duplicates. ‘0’ is the first duplicated character. It has hex value 0x30 and is at index 25. This is a duplicate of the character at index 10. [1] FALSE
#langracket(define(first-non-unique-element.indexseq)(let/ecret(for/fold((es(hash)))((eseq)(i(in-naturals)))(if(hash-has-key?ese)(ret(liste(hash-refese)i))(hash-setesei)))#f))(define(report-if-a-string-has-all-unique-charactersstr)(printf"~s (length ~a): ~a~%"str(string-lengthstr)(match(first-non-unique-element.indexstr)[#f"contains all unique characters"][(listeii′)(format"has character '~a' (0x~a) at index ~a (first seen at ~a)"e(number->string(char->integere)16)i′i)])))(module+main(for-eachreport-if-a-string-has-all-unique-characters(list""".""abcABC""XYZ ZYX""1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ")))
"" (length 0): contains all unique characters"." (length 1): contains all unique characters"abcABC" (length 6): contains all unique characters"XYZ ZYX" (length 7): has character 'Z' (0x5a) at index 4 (first seen at 2)"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (length 36): has character '0' (0x30) at index 24 (first seen at 9)
(formerly Perl 6)
Raku works with unicode natively and handles combining characters and multi-byte emoji correctly. In the last string, notice the the length is correctly shown as 11 characters and that the delta with a combining circumflex in position 6 is not the same as the deltas without in positions 5 & 9.
->$str {my$i =0;print"\n{$str.raku} (length: {$str.chars}), has ";my%m =$str.comb.Bag;ifany(%m.values) >1 {say"duplicated characters:";say"'{.key}' ({.key.uninames}; hex ordinal: {(.key.ords).fmt: "0x%X"})" ~" in positions: {.value.join: ', '}"for%m.grep( *.value >1 ).sort( *.value[0] ); }else {say"no duplicated characters." }}for'','.','abcABC','XYZ ZYX','1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ','01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X','🦋🙂👨👩👧👦🙄ΔΔ̂ 🦋Δ👍👨👩👧👦'
"" (length: 0), has no duplicated characters."." (length: 1), has no duplicated characters."abcABC" (length: 6), has no duplicated characters."XYZ ZYX" (length: 7), has duplicated characters:'X' (LATIN CAPITAL LETTER X; hex ordinal: 0x58) in positions: 1, 7'Y' (LATIN CAPITAL LETTER Y; hex ordinal: 0x59) in positions: 2, 6'Z' (LATIN CAPITAL LETTER Z; hex ordinal: 0x5A) in positions: 3, 5"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (length: 36), has duplicated characters:'0' (DIGIT ZERO; hex ordinal: 0x30) in positions: 10, 25"01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X" (length: 39), has duplicated characters:'0' (DIGIT ZERO; hex ordinal: 0x30) in positions: 1, 11, 26, 38'X' (LATIN CAPITAL LETTER X; hex ordinal: 0x58) in positions: 35, 39"🦋🙂👨👩👧👦🙄ΔΔ̂ 🦋Δ👍👨👩👧👦" (length: 11), has duplicated characters:'🦋' (BUTTERFLY; hex ordinal: 0x1F98B) in positions: 1, 8'👨👩👧👦' (MAN ZERO WIDTH JOINER WOMAN ZERO WIDTH JOINER GIRL ZERO WIDTH JOINER BOY; hex ordinal: 0x1F468 0x200D 0x1F469 0x200D 0x1F467 0x200D 0x1F466) in positions: 3, 11'Δ' (GREEK CAPITAL LETTER DELTA; hex ordinal: 0x394) in positions: 5, 9
/*REXX pgm determines if a string is comprised of all unique characters (no duplicates).*/@.=/*assign a default for the @. array. */parsearg@.1/*obtain optional argument from the CL.*/if@.1=''thendo;@.1=/*Not specified? Then assume defaults.*/@.2=.@.3='abcABC'@.4='XYZ ZYX'@.5='1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ'enddoj=1;ifj\==1&@.j==''thenleave/*String is null & not j=1? We're done*/saycopies('─',79)/*display a separator line (a fence). */say'Testing for the string (length'length(@.j)"): "@.jsaydup=isUnique(@.j)say'The characters in the string'word("are aren't",1+(dup>0))'all unique.'ifdup==0theniterate?=substr(@.j,dup,1)say'The character '?" ('"c2x(?)"'x) at position "dup,' is repeated at position 'pos(?,@.j,dup+1)end/*j*/exit/*stick a fork in it, we're all done. *//*──────────────────────────────────────────────────────────────────────────────────────*/isUnique:procedure;parseargx/*obtain the character string.*/dok=1tolength(x)-1/*examine all but the last. */p=pos(substr(x,k,1),x,k+1)/*see if the Kth char is a dup*/ifp\==0thenreturnk/*Find a dup? Return location.*/end/*k*/return0/*indicate all chars unique. */
───────────────────────────────────────────────────────────────────────────────Testing for the string (length 0):The characters in the string are all unique.───────────────────────────────────────────────────────────────────────────────Testing for the string (length 1): .The characters in the string are all unique.───────────────────────────────────────────────────────────────────────────────Testing for the string (length 6): abcABCThe characters in the string are all unique.───────────────────────────────────────────────────────────────────────────────Testing for the string (length 7): XYZ ZYXThe characters in the string aren't all unique.The character X ('58'x) at position 1 is repeated at position 7───────────────────────────────────────────────────────────────────────────────Testing for the string (length 36): 1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZThe characters in the string aren't all unique.The character 0 ('30'x) at position 10 is repeated at position 25
inputStr = ["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"] for Str in inputStr for x = 1 to len(Str) for y = x + 1 to len(Str) if Str[x] = Str[y] char = Str[x] ? "Input = " + "'" + Str + "'" + ", length = " + len(Str) ? " First duplicate at positions " + x + " and " + y + ", character = " + "'" + char + "'" loop 3 ok next next ? "Input = " + "'" + Str + "'" + ", length = " + len(Str) ? " All characters are unique."next
Input = '', length = 0 All characters are unique.Input = '.', length = 1 All characters are unique.Input = 'abcABC', length = 6 All characters are unique.Input = 'XYZ ZYX', length = 7 First duplicate at positions 1 and 7, character = 'X'Input = '1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ', length = 36 First duplicate at positions 10 and 25, character = '0'
RPL code | Comment |
---|---|
≪ → string ≪ "All chars unique" "" 1 string SIZEFOR j string j DUP SUBIF DUP2 POSTHEN DUP " duplicated at " + string ROT POS →STR + " and " + j →STR + ROT DROP SWAP string SIZE 'j' STOELSE +END NEXT DROP≫ ≫ 'UNICH?' STO | UNICH?( "string" -- "report" )initialize stackscan string extract jth character if already seen generate report . . exit loop else add the char to already seen listclean stack. |
≪ { "" "." "abcABC" "XYZ ZYX" "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" } → cases ≪ 1 cases SIZE FOR n cases n GET UNICH? NEXT≫ ≫ ´TASK’ STO
5: "All chars unique"4: "All chars unique"3: "All chars unique"2: "Z duplicated at 3 and 5" 1: "0 duplicated at 10 and 25"
strings=["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ","01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X","hétérogénéité","🎆🎃🎇🎈","😍😀🙌💃😍🙌","🐠🐟🐡🦈🐬🐳🐋🐡",]strings.eachdo|str|seen={}print"#{str.inspect} (size#{str.size}) "res="has no duplicates."#may changestr.chars.each_with_indexdo|c,i|ifseen[c].nil?seen[c]=ielseres="has duplicate char#{c} (#{'%#x'%c.ord}) on#{seen[c]} and#{i}."breakendendputsresend
"" (size 0) has no duplicates."." (size 1) has no duplicates."abcABC" (size 6) has no duplicates."XYZ ZYX" (size 7) has duplicate char Z (0x5a) on 2 and 4."1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (size 36) has duplicate char 0 (0x30) on 9 and 24."01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X" (size 39) has duplicate char 0 (0x30) on 0 and 10."hétérogénéité" (size 13) has duplicate char é (0xe9) on 1 and 3."🎆🎃🎇🎈" (size 4) has no duplicates."😍😀🙌💃😍🙌" (size 6) has duplicate char 😍 (0x1f60d) on 0 and 4."🐠🐟🐡🦈🐬🐳🐋🐡" (size 8) has duplicate char 🐡 (0x1f421) on 2 and 7.
fnunique(s:&str)->Option<(usize,usize,char)>{s.chars().enumerate().find_map(|(i,c)|{s.chars().enumerate().skip(i+1).find(|(_,other)|c==*other).map(|(j,_)|(i,j,c))})}fnmain(){letstrings=["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ","01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X","hétérogénéité","🎆🎃🎇🎈","😍😀🙌💃😍🙌","🐠🐟🐡🦈🐬🐳🐋🐡",];forstringin&strings{print!("\"{}\" (length {})",string,string.chars().count());matchunique(string){None=>println!(" is unique"),Some((i,j,c))=>println!(" is not unique\n\tfirst duplicate:\"{}\" (U+{:0>4X}) at indices {} and {}",c,casusize,i,j),}}}
"" (length 0) is unique"." (length 1) is unique"abcABC" (length 6) is unique"XYZ ZYX" (length 7) is not uniquefirst duplicate: "X" (U+0058) at indices 0 and 6"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (length 36) is not uniquefirst duplicate: "0" (U+0030) at indices 9 and 24"01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X" (length 39) is not uniquefirst duplicate: "0" (U+0030) at indices 0 and 10"hétérogénéité" (length 13) is not uniquefirst duplicate: "é" (U+00E9) at indices 1 and 3"🎆🎃🎇🎈" (length 4) is unique"😍😀🙌💃😍🙌" (length 6) is not uniquefirst duplicate: "😍" (U+1F60D) at indices 0 and 4"🐠🐟🐡🦈🐬🐳🐋🐡" (length 8) is not uniquefirst duplicate: "🐡" (U+1F421) at indices 2 and 7
commentReturn0iftherearenorepeatedcharactersins(includingthespecialcaseofanemptystring),otherwisethefirstpositionwhereacharacterduplicatesonepreviouslyencounteredendfunctionrepeated_chars(s=string)=integervari,j,slen,result=integerslen=len(s)ifslen<2thenresult=0elsebeginresult=0fori=1toslen-1forj=i+1toslenifmid(s,i,1)=mid(s,j,1)andresult=0thenresult=jnextjnextiendend=resultprocedurereport(str=string)varp,first=integerp=repeated_chars(str)ifp=0thenprintchr(34);str;chr(34);" (length =";len(str);\") has no duplicate characters"elsebeginfirst=instr(1,str,mid(str,p,1))printchr(34);str;chr(34);" (length =";len(str);\") has duplicate characters:"print"'";mid(str,p,1);"' (= ";right$(hex$(asc(mid(str,p,1))),2);\"h)";" appears at positions";first;" and";pendprintendrem-testcasesreport""report"."report"abcABC"report"XYZ ZYX"report"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"end
"" (length = 0) has no duplicate characters"." (length = 1) has no duplicate characters"abcABC" (length = 6) has no duplicate characters"XYZ ZYX" (length = 7) has duplicate characters:'X' (= 58h) appears at positions 1 and 7"1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" (length = 36) has duplicate characters:'0' (= 30h) appears at positions 10 and 25
funcindex_duplicates(str){gather{fork,vin(str.chars.kv){vari=str.index(v,k+1)take([k,i])if(i!=-1)}}}varstrings=["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ","01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X","hétérogénéité","🎆🎃🎇🎈","😍😀🙌💃😍🙌","🐠🐟🐡🦈🐬🐳🐋🐡"]strings.each{|str|print"\n'#{str}' (size:#{str.len}) "vardups=index_duplicates(str)say"has duplicated characters:"ifdupsfori,jin(dups){say"#{str[i]} (#{'%#x'%str[i].ord}) in positions:#{i},#{j}"}say"has no duplicates."if!dups}
'' (size: 0) has no duplicates.'.' (size: 1) has no duplicates.'abcABC' (size: 6) has no duplicates.'XYZ ZYX' (size: 7) has duplicated characters:X (0x58) in positions: 0, 6Y (0x59) in positions: 1, 5Z (0x5a) in positions: 2, 4'1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ' (size: 36) has duplicated characters:0 (0x30) in positions: 9, 24'01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X' (size: 39) has duplicated characters:0 (0x30) in positions: 0, 100 (0x30) in positions: 10, 250 (0x30) in positions: 25, 37X (0x58) in positions: 34, 38'hétérogénéité' (size: 13) has duplicated characters:é (0xe9) in positions: 1, 3t (0x74) in positions: 2, 11é (0xe9) in positions: 3, 7é (0xe9) in positions: 7, 9é (0xe9) in positions: 9, 12'🎆🎃🎇🎈' (size: 4) has no duplicates.'😍😀🙌💃😍🙌' (size: 6) has duplicated characters:😍 (0x1f60d) in positions: 0, 4🙌 (0x1f64c) in positions: 2, 5'🐠🐟🐡🦈🐬🐳🐋🐡' (size: 8) has duplicated characters:🐡 (0x1f421) in positions: 2, 7
packagerequireTcl8.6;# For binary encodearraysetyesno{1Yes2No}settest{{}{.}{abcABC}{XYZZYX}{1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ}{hétérogénéité}}# Loop through test stringsforeachstr$test{setchars[dictcreate];# init dictionarysetnum_chars1;# In case of empty string# Loop through characters in stringfor{seti0}{$i<[stringlength$str]}{incri}{setc[stringindex$str$i];# get char at indexdictlappendchars$c$i;# add index to a running list for key=charsetindexes[dictget$chars$c];# get the whole running listsetnum_chars[llength$indexes];# count the # of indexesif{$num_chars>1}{break;# Found a duplicate, break out of the loop}}# Handle Outputputs[format"Tested: %38s (len: %2d). All unique? %3s. "\"'$str'"[stringlength$str]$yesno($num_chars)]if{$num_chars>1}{puts[format" --> Character '%s' (hex: 0x%s) reappears at indexes: %s."\$c[binaryencodehex$c]$indexes]}}
Tested: '' (len: 0). All unique? Yes.Tested: '.' (len: 1). All unique? Yes.Tested: 'abcABC' (len: 6). All unique? Yes.Tested: 'XYZ ZYX' (len: 7). All unique? No. --> Character 'Z' (hex: 0x5a) reappears at indexes: 2 4.Tested: '1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ' (len: 36). All unique? No. --> Character '0' (hex: 0x30) reappears at indexes: 9 24.Tested: 'hétérogénéité' (len: 13). All unique? No. --> Character 'é' (hex: 0xe9) reappears at indexes: 1 3.
fn analyze(s string) { chars := s.runes() le := chars.len println("Analyzing $s which has a length of $le:") if le > 1 { for i := 0; i < le-1; i++ { for j := i + 1; j < le; j++ { if chars[j] == chars[i] { println(" Not all characters in the string are unique.") println(" '${chars[i]}'' (0x${chars[i]:x}) is duplicated at positions ${i+1} and ${j+1}.\n") return } } } } println(" All characters in the string are unique.\n")} fn main() { strings := [ "", ".", "abcABC", "XYZ ZYX", "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ", "01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X", "hétérogénéité", "🎆🎃🎇🎈", "😍😀🙌💃😍🙌", "🐠🐟🐡🦈🐬🐳🐋🐡", ] for s in strings { analyze(s) }}
Analyzing which has a length of 0: All characters in the string are unique.Analyzing . which has a length of 1: All characters in the string are unique.Analyzing abcABC which has a length of 6: All characters in the string are unique.Analyzing XYZ ZYX which has a length of 7: Not all characters in the string are unique. 'X'' (0x58) is duplicated at positions 1 and 7.Analyzing 1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ which has a length of 36: Not all characters in the string are unique. '0'' (0x30) is duplicated at positions 10 and 25.Analyzing 01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X which has a length of 39: Not all characters in the string are unique. '0'' (0x30) is duplicated at positions 1 and 11.Analyzing hétérogénéité which has a length of 13: Not all characters in the string are unique. 'é'' (0xe9) is duplicated at positions 2 and 4.Analyzing 🎆🎃🎇🎈 which has a length of 4: All characters in the string are unique.Analyzing 😍😀🙌💃😍🙌 which has a length of 6: Not all characters in the string are unique. '😍'' (0x1f60d) is duplicated at positions 1 and 5.Analyzing 🐠🐟🐡🦈🐬🐳🐋🐡 which has a length of 8: Not all characters in the string are unique. '🐡'' (0x1f421) is duplicated at positions 3 and 8.
import"./fmt"forConv,Fmtvaranalyze=Fn.new{|s|varchars=s.codePoints.toListvarle=chars.countSystem.print("Analyzing%(Fmt.q(s)) which has a length of%(le):")if(le>1){for(iin0...le-1){for(jini+1...le){if(chars[j]==chars[i]){System.print(" Not all characters in the string are unique.")varc=String.fromCodePoint(chars[i])varhex="0x"+Conv.hex(chars[i])System.print(" '%(c)' (%(hex)) is duplicated at positions%(i+1) and%(j+1).\n")return}}}}System.print(" All characters in the string are unique.\n")}varstrings=["",".","abcABC","XYZ ZYX","1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ","01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X","hétérogénéité","🎆🎃🎇🎈","😍😀🙌💃😍🙌","🐠🐟🐡🦈🐬🐳🐋🐡"]for(sinstrings)analyze.call(s)
Analyzing "" which has a length of 0: All characters in the string are unique.Analyzing "." which has a length of 1: All characters in the string are unique.Analyzing "abcABC" which has a length of 6: All characters in the string are unique.Analyzing "XYZ ZYX" which has a length of 7: Not all characters in the string are unique. 'X' (0x58) is duplicated at positions 1 and 7.Analyzing "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" which has a length of 36: Not all characters in the string are unique. '0' (0x30) is duplicated at positions 10 and 25.Analyzing "01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X" which has a length of 39: Not all characters in the string are unique. '0' (0x30) is duplicated at positions 1 and 11.Analyzing "hétérogénéité" which has a length of 13: Not all characters in the string are unique. 'é' (0xe9) is duplicated at positions 2 and 4.Analyzing "🎆🎃🎇🎈" which has a length of 4: All characters in the string are unique.Analyzing "😍😀🙌💃😍🙌" which has a length of 6: Not all characters in the string are unique. '😍' (0x1f60d) is duplicated at positions 1 and 5.Analyzing "🐠🐟🐡🦈🐬🐳🐋🐡" which has a length of 8: Not all characters in the string are unique. '🐡' (0x1f421) is duplicated at positions 3 and 8.
include xpllib; \contains StrLen functionproc StrUnique(S); \Show if string has unique charschar S;int L, I, J, K;[L:= StrLen(S);IntOut(0, L); Text(0, ": ^""); Text(0, S); ChOut(0, ^"); CrLf(0);for I:= 0 to L-1 do for J:= I+1 to L-1 do [if S(I) = S(J) then [ChOut(0, \tab\ 9); for K:= 0 to I do ChOut(0, ^ ); ChOut(0, ^^); for K:= 0 to J-I-2 do ChOut(0, ^ ); ChOut(0, ^^); Text(0, " Duplicate character: "); ChOut(0, S(I)); Text(0, ", hex "); SetHexDigits(2); HexOut(0, S(I)); CrLf(0); return; ]; ];Text(0, " Unique, no duplicates"); CrLf(0);];[Text(0, "Length"); CrLf(0);StrUnique("");StrUnique(".");StrUnique("abcABC");StrUnique("XYZ ZYX");StrUnique("1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ");StrUnique("thequickbrownfoxjumps");]
Length0: "" Unique, no duplicates1: "." Unique, no duplicates6: "abcABC" Unique, no duplicates7: "XYZ ZYX" ^ ^ Duplicate character: X, hex 5836: "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ" ^ ^ Duplicate character: 0, hex 3021: "thequickbrownfoxjumps" ^ ^ Duplicate character: u, hex 75
fcn stringUniqueness(str){ // Does not handle Unicode sz,unique,uz,counts := str.len(), str.unique(), unique.len(), str.counts(); println("Length %d: \"%s\"".fmt(sz,str)); if(sz==uz or uz==1) println("\tAll characters are unique"); else // counts is (char,count, char,count, ...) println("\tDuplicate: ", counts.pump(List,Void.Read,fcn(str,c,n){ if(n>1){ is,z:=List(),-1; do(n){ is.append(z=str.find(c,z+1)) } "'%s' (0x%x)[%s]".fmt(c,c.toAsc(),is.concat(",")) } else Void.Skip }.fp(str)).concat(", "));}
testStrings:=T("", ".", "abcABC", "XYZ ZYX", "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ", "01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X");foreach s in (testStrings){ stringUniqueness(s) }
Length 0: ""All characters are uniqueLength 1: "."All characters are uniqueLength 6: "abcABC"All characters are uniqueLength 7: "XYZ ZYX"Duplicate: 'X' (0x58)[0,6], 'Y' (0x59)[1,5], 'Z' (0x5a)[2,4]Length 36: "1234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ"Duplicate: '0' (0x30)[9,24]Length 39: "01234567890ABCDEFGHIJKLMN0PQRSTUVWXYZ0X"Duplicate: '0' (0x30)[0,10,25,37], 'X' (0x58)[34,38]