Parse String to list of binary tuples - string

I'm trying to parse a string "A1B2C3D4" to [('A',1),('B',2),('C',3)] in Haskell.
I'm trying to use a map like this map (\[a, b] -> (a :: Char, b :: Int)) x where x is the string.
This is the function signature I need to follow :: String -> [(Char, Int)].
Unfortunately i'm getting type mismatches, can anyone give any hint how to solve this?
I'm in the right direction?

Well, map is really meant for applying a single function to every element of something, one-by-one. Splitting the string how you want requires context (knowing the next letter), so map isn't the best choice here.
However, you said your solution is required to be in terms of map. It can be done, but it's a bit roundabout. I couldn't think of any way to make map split the actual string, but it can certainly be used to transform it to the correct type:
isDigit :: Char -> Bool
isDigit c = elem c ['0'..'9']
split :: String -> [(Char, Int)]
split str = let chars = filter (not . isDigit) str
nums = filter isDigit str
zipped = zip chars nums in
map (\(a, b) -> (a, read [b])) zipped

There's a few problems.
The pattern [a, b] in map (\[a, b] -> ...) x only matches lists of two elements, so the compiler infers that the function \[a, b] -> ... has type [r] -> s for some r and s.
The compiler knows that map has the type (u -> v) -> [u] -> [v], so it unifies u with [r] and v with s to infer the type [[r]] -> [s] for map (\[a, b] -> ...).
This means x must have type [[r]], that is, it must be a list of lists. But you want x to be a String which is a synonym for [Char]. The compiler can't unify [[r]] and [Char], so it objects.
You're attempting to "cast" a to a Char and b to an Int like you would in C, but you can't do that in Haskell. If you want to convert a Char like '1' into the Int 1, you need a different approach, like read, which you can use to convert from a String to an Int.
Here's some advice. Don't use map. Try writing a recursive solution instead.
Start by considering a few cases:
what does myParser "" return?
what does myParser "a1" return?
what does myParser [a,b] return?
what does myParser (a:b:cs) return?

I came up with this but it's really not safe as it doesn't handle incorrect string like "AA11B2C3"!
splitingN :: Int -> [a] -> [[a]]
splitingN _ [] = []
splitingN n l
| n > 0 = take n l : splitingN n (drop n l)
| otherwise = error "uhhhhhh"
tuplify :: String -> (Char, Int)
tuplify a = (head a, read $ tail a)
stringy :: String -> [(Char, Int)]
stringy s = tuplify <$> splitingN 2 s
> stringy "A1B2C3D4" == [('A',1),('B',2),('C',3),('D',4)]
A much nicer way but still not fully safe would be:
stringy :: [a] -> [(a, a)]
stringy [] = []
stringy (a : b : rest) = (a, b) : splitting rest
stringy [a] = error "uhhhhh"
Should really check if a and b from (a : b : rest) are indeed Char & Int. Also this uses recursion and you mentioned using map so might not suffice and it's pretty polymorphic in it's types.

As others have pointed out, you need to understand that map applies the given function over each member of the list. Once you understand that, you will realize that there is no way you can get the conversion you want by applying a function on the existing list.
This leads to realization that once you have a list of "A1", "B2",... then you can take these and convert it using a map function.
I have given the code for function below. The split' function is not safe as it can blow up in lot of cases (expected a string which can be perfectly split into 2 chars). I am also using the function digitToInt, for which you need to import Data.Char. You did say you want no import, in that case you can write your own digitToInt function, look into the library code, it is fairly straightforward.
import Data.Char
split' :: String -> [String]
split' [] = []
split' (x:y:xs) = (x:[y]) : split' xs
convert :: String -> [(Char, Int)]
convert input = map (\s -> (s!!0 , digitToInt(s!!1) )) $ split' input

Related

list of Data to String

So I have a list of Data, I know newtype is currently better but I will add more things to it. I would like to convert a list of Pack to a String.
unpack [Pack ('a','b'), Pack ('c','d') , Pack (' ', 'e') ] = "abcd e"
I was thinking about using a foldl but am stuck trying to figure it out.
data Pack= Pack (Char, Char) deriving ( Show)
unPack:: [Pack] -> String
unpack list = foldr (\Pack (a,b) -> show a + show b -> concat) "" list
Thx for the helping
To pattern-patch on Pack xyz in a lambda, you need to put it in parentheses:
foldr (\(Pack (a,b)) -> ...)
What you wrote would actually parse as two separate arguments
foldr (\(Pack) -> \(a,b) -> ...)
Next, you can't concatenate strings with +, that's for numbers. ++ or <> are for lists / strings.
Then, the -> concat isn't valid syntax. What you want to do is concatenate the remainder of the foldr computation to the shown a and b. That remainder is the second argument of the folding function:
foldr (\(Pack (a,b)) rest -> show a ++ show b ++ rest)
...or shorter,
foldr (\(Pack (a,b)) -> shows a . shows b)
Your Pack type is isomorphic to two-character strings:
pack2String :: Pack -> String
pack2String (Pack (a,b)) = a:[b]
string2Pack :: String -> Pack -- partial, since String isn't limited in length
string2Pack (a:[b]) = Pack (a, b)
(Note that Pack (a,b) already adds an unnecessary level of wrapping; data Pack = Pack Char Char is also isomorphic to Pack (Char, Char).)
As such, you don't actually need foldr; you can use the list monad instead.
unpack :: [Pack] -> String
unpack xs = xs >>= pack2String
If you aren't yet comfortable with monads, you can just use the concatMap function directly:
unpack :: [Pack] -> String
unpack = concatMap pack2String

Taking an input string and return a string list of only the words that start with "ba"?

I'm trying to write a code in which would take a input string say:
I love bacon, but I love bananas more.
and return ["bacon","bananas"] as output.
However I've ran into some troubles with my code, as I can't seem to properly implement this, currently my idea is that I would input a string and then use word() to split up the string into a string list, and then call getWrods to extract all the words with "ba" as their prefix and then return a list composed of words that start with "ba" for the main function allWords.
My code is as follows:
getWords:: String -> [String] -> [String]
getWords n [] = []
getWords n (x:xs)
| n isPrefixOf x = [x] ++ getWords n xs
|otherwise = getWords n xs
allWordss:: String -> [String]
allWordss n = getWords("ba" words(n))
I think that by using filter :: (a -> Bool) -> [a] -> [a] here, you make the problem easier.
You can as filter condition use - like in your code isPrefixOf :: Eq a => [a] -> [a] -> Bool, but you here wrote in in "infix" notation, but without writing backticks. You thus can call the function with:
isPrefixOf n x
or:
n `isPrefixOf` x
A final problem with your code is that you write:
getWords("ba" words(n))
Here you seem to call a function with brackets, which is quite common in languages like Java, C++, etc. In Haskell however, a function f is called with a parameter x like f x, so you make a call with:
getWords "ba" (words n)
If we use filter here, we thus obtain:
allBaWords :: String -> [String]
allBaWords n = filter (\x -> isPrefixOf "ba" x) (words n)
or shorter:
allBaWords :: String -> [String]
allBaWords = filter (isPrefixOf "ba") . words
We can break up the problem into three logical parts:
Separate a string into a list of words.
Recognize whether a word starts with "ba".
Given a list, get a list of all the elements that satisfy a certain condition (often called a predicate).
Let's start by importing a couple standard modules:
import Data.List (isPrefixOf)
import Data.String (words)
Let's start with (2):
startsWithBa :: String -> Bool
startsWithBa s = -- something using isPrefixOf
As others have noted, you have to enclose isPrefixOf in backticks if you want to use it infix (which most people tend to do so it reads nicely).
Now to separate the string into words, we use
words :: String -> [String]
To extract just the strings that start with "ba", we can use the function
filter :: (a -> Bool) -> [a] -> [a]
I'll let you try to put these pieces together.

Haskell, List as input for a function, How?

I've been given the following question in my coursework;
Define a function
flatten :: [(Char,Int)] -> String
that flattens a list of pairs of characters and digits to a string. For example:
flatten [('a',5),('b',4),('c',2)]
"a5b4c2"
flatten [('d',9),('d',3)]
"d9d3"
My problem is that whenever I attempt to define this function i get a type error relating the the [(Char, Int)] input. For example;
Couldn't match type '(Char, Int)' with '[Char]'
Expected type: [[Char]]
Actual type: [(Char, Int)]
I've tried more ways of writing this definition in more ways than I can count, so I don't have any particular code to show, or any particular error ( I kept getting different ones...so many). All i have so far is;
flatten :: [(Char, Int)] -> String
flatten [] = []
i figure my next line should go something like;
flatten ???? = concat (????)
but I have no idea what to put in place of these question marks and Google search/class notes give no examples to follow.
any ideas?
Well it is clear that in the case the list is not empty, it is of the form ((ca,cb):cs) with ca the Char, cb the Int and cs the remainder of the list [(Char,Int)].
In that case we can simply construct a string for that sequence ca:(show cb) with show :: Show a => a -> String we convert an integer to its String counterpart. Next we concatenate the flattening of remainder of the list to that string, so:
flatten ((ca,cb):cs) = ca:(show cb ++ flatten cs)
Or in full:
flatten :: [(Char, Int)] -> String
flatten [] = []
flatten ((ca,cb):cs) = ca:(show cb ++ flatten cs)
First of all, we try to create a String from a (Char, Int). If we can do that we've almost done, since we can do that for all (Char, Int). So let's transform a single (Char, Int):
flattenSingle :: (Char, Int) -> String
flattenSingle (c, i) = c : show i
Now, we need to do that for all entries:
flattenAll :: [(Char, Int)] -> [String]
flattenAll xs = map flattenSingle xs
And last, but not least, we need to concat the [String] (which is a [[Char]]) to a String (which is a [Char]):
flatten :: [(Char, Int)] -> String
flatten xs = concat (flattenAll xs)
And we're done. How did we do that? Well, we've started with a much easier problem, namely how to get a single String from a (Char, Int), and used that to get our result.
Here's everything in a single function:
flatten = concat . map flattenSingle
where
flattenSingle (c, i) = c : show i
Since concat . map f is often used, there's a function for that, called concatMap:
flatten :: [(Char, Int)] -> String
flatten = concatMap flattenSingle
where
flattenSingle (c, i) = c : show i
Let’s think about what goes into flatten and what comes out of it.
flatten, takes a list of pairs of type: (Char, Int) and produces a [Char]; it produces a list from an existing list. Does this ring a bell?
flatten xs = [ c | (char, int) <- xs, c <-[char] ++ show int]
We can sequentially deconstruct each pair in the given list; for each pair, we turn each component into a string so we can concatenate them. Now we have a string for each pair, we just need to take each character out to produce the final string.
flatten = mconcat. map (\(c,i) -> [c] ++ show i)
You might also use foldl to make your intention very clear:
a=[('a',5),('b',4),('c',2)]
f b (x,y)=b++[x]++(show y)
result=foldl f "" a
Or you can make it a one-liner:
Solution 1:
foldl (\b (x,y)->b++[x]++(show y)) "" a
Solution 2:
concat $ map (\(x,y)->[x]++show y) a
Solution 3: (Being more efficient compared to solution 1)
foldr (\(x,y) b->b++[x]++(show y)) "" a

Replacing strings with strings from a list

I am trying to write a function that takes a list of searchwords, a list of replacementwords and a string on which those will be used.
listReplace :: [String] -> [String] -> String -> String
The tricky part is that if the fitting searchword is the n'th, then the n'th replacementword should be used. Also, when a replacementword has been used it should not be replaced by a different replacementword if it is actually a searchword itself. I've already written these kind of functions for
replace :: String -> String -> String -> String:
replace x y [] = []
replace x y (z:zs) = if isPrefixOf x (z:zs) then y ++ replace x y (drop (length x) (z:zs)) else z: (replace x y zs)
and
replace' :: String -> [String] -> String -> String:
replace' x y [] = []
replace' x [] (z:zs) = []
replace' x y (z:zs) = if isPrefixOf x (z:zs) then concat (take 1 y) ++ replace' x (drop 1 y) (drop (length x) (z:zs)) else z: (replace' x y zs)
I just dont know how to begin with this replaceList function tho, the only thing that might actually be useful that I've found so far is a function that replaces the n'th element in a list. But I cant seem to figure out how to put it to use in this case:
replace :: Int -> a -> [a] -> [a]
replace n a [] = []
replace 0 a (x:xs) = a : xs
replace n a (x:xs) = x : replace (n-1) a xs
well hopefully one of you can help me out! Thanks in advance :)
I would suggest a different type than
listReplace :: [String] -> [String] -> String -> String
What would happen if one called
listReplace ["one", "two"] ["een"] "I have two problems"
the substring "two" would be found, but there's no replacement for it provided.
Rather use
listReplace :: [(String, String)] -> String -> String
so that you are guaranteed that there are always exactly as many replacement strings as patterns you search for.
A simple implementation could then use
find :: (a -> Bool) -> [a] -> Maybe a
from Data.List to check if any of the provided patterns is a prefix of the remaining input,
listReplace _ "" = ""
listReplace replacements string#(c:cs)
= case find ((`isPrefixOf` string) . fst) replacements of
Just (pat,rep) -> rep ++ listReplace replacements (drop (length pat) string)
Nothing -> c : listReplace replacements cs
This easy solution is not very efficient - that would require a more complicated algorithm - and it doesn't detect if one of the patterns to be replaced is a prefix of another, so that if the shorter pattern comes before the longer in the list, the longer pattern would never be used, even if it should be. That can be dealt with by sorting the list of replacements, for example descending by lexicographical order, before calling the replace function.
My suggestion would be to use a somewhat different intermediate datastructure when processing the string that you want edited. Here is a solution that uses tries.
Preliminaries
import Data.Map (Map)
import qualified Data.Map as M
Tries
Here is a simple datatype of tries:
data Trie = Trie (Maybe String) (Map Char Trie)
Tries are constructed from the empty trie and a function for inserting key/value bindings into an existing trie:
empty :: Trie
empty = Trie Nothing M.empty
insert :: String -> String -> Trie -> Trie
insert [] val (Trie _ tries) = Trie (Just val) tries
insert (c : cs) val (Trie mbVal tries) = case M.lookup c tries of
Nothing -> Trie mbVal (M.insert c (insert cs val empty) tries)
Just trie -> Trie mbVal (M.insert c (insert cs val trie) tries)
Matching
With tries, matching reduces to recursing over the input string while traversing the trie. When a match is found, the corresponding replacement value is returned together with the remaining part of the input string (so that it can be subjected to further replacements):
match :: Trie -> String -> Maybe (String, String)
match (Trie (Just val) _ ) s = Just (val, s)
match (Trie Nothing _ ) [] = Nothing
match (Trie Nothing tries) (c : cs) = case M.lookup c tries of
Nothing -> Nothing
Just trie -> match trie cs
Note that this function is greedy in the sense that it gives preference to the shortest match if multiple matches are possible. Adapting it so that it picks the longest match instead (and, hence, implements the "maximal-munch" principle) is not too hard.
Replacement
Replacing occurrences of search words by their corresponding replacements can be implemented by looking for a match in the input string: if a match is found, the replacement is put into the output string and we continue processing with the unmatched part of the string. If no match is found, we keep the head of the input string and proceed with the tail.
replace :: Trie -> String -> String
replace trie = go
where
go [] = []
go s#(c : cs) = case match trie s of
Nothing -> c : go cs
Just (s', s'') -> s' ++ go s''
Bringing it all together
Your required function listReplace is now almost trivial:
listReplace :: [String] -> [String] -> String -> String
listReplace keys vals = replace trie
where
trie = foldr ($) empty (zipWith insert keys vals)
As you see, the part that you refer to as "tricky" is easily realised by "zipping" the two list arguments.
Example
Here is a simple example (inspired by L. Peter Deutsch):
> let s = "to err is human; to forgive, divine"
> listReplace ["err", "forgive"] ["iterate", "recurse"] s
"to iterate is human; to recurse, divine"

Swap characters between strings Haskell

if i say i have two strings or character lists,
list1 = ["c","a","t"]
list2 = ["d","o","g"]
and if i read a string using Input Output "ct" and pass it to the function,the function should return "dg".
Please give me any idea about such a function.
I would consider taking those two lists, zipping them together, use Data.Map.fromList to create a lookup Map, then map over the input String and use the Map to work out what to replace them with.
I'll first assume list1 and list2 have type [Char] (i.e. String), since that's what your text seems to indicate (your code has them as [String]s -- if you really want this, see the generalized version in the addendum).
If you zip the two lists, you end up with a list of pairs indicating how to translate characters. In your example, zip list1 list2 = [('c','d'), ('a','o'), ('t','g')]. We'll call this our lookup list. Now consider the function lookup:
lookup :: Eq a => a -> [(a, b)] -> Maybe b
In our case, we can specialize this to
lookup :: Char -> [(Char, Char)] -> Maybe Char
so we have something that takes a character and a lookup list and returns a substituted character if the input character is in the lookup list (otherwise a Nothing). Now we just need to glue the things we've found together: We essentially need to map \c -> lookup c lookupList (more elegantly written as flip lookup) over the input string while throwing out any characters not found in the lookup list. Well, enter mapMaybe:
mapMaybe :: (a -> Maybe b) -> [a] -> [b]
It does exactly what we want. Now your function can be written as
replace :: String -> String -> String -> String
replace list1 list2 = mapMaybe ((flip lookup) (zip list1 list2))
You'll need to import Data.Maybe.
Addendum, for when you understand the above: Observe how what we did above had nothing to do with the fact that we were working with lists of characters. We could do everything above with lists of any type for which equality makes sense, i.e. for (lists of) any type which is an instance of the Eq typeclass (cf the signature of lookup above). Moreover, we don't have to translate from that type to itself -- for example, each character above could be sent to say, an integer! So really, we can write
replace :: (Eq a) => [a] -> [b] -> [a] -> [b]
replace list1 list2 = mapMaybe ((flip lookup) (zip list1 list2))
and now our function works as long as list1 is a list of something for which equality makes sense. Replacement of characters just becomes a special case.
A quick example:
> replace "cat" "dog" "ct"
"dg"
> replace "cat" [1,2,3] "ct"
[1,3]
For two string you may do as follows:
patt :: String -> String -> String -> String
patt (x : xs) (y : ys) p'#(p : ps)
| p == x = y : patt xs ys ps
| otherwise = patt xs ys p'
patt _ _ [] = []
main :: IO ()
main = do
putStrLn $ patt "cat" "dog" "ct"

Resources