
I am relatively new to Haskell, having spent the last half a decade or so developing in Ruby. I am attempting to (for the sake of exercise) implement a split function from the ground up in Haskell, and for the life of me I can not figure out why it doesn't work. Without further ado: module MyAwesomeModule where import qualified Data.Text as T outputSplit :: String -> [String] -> IO () outputSplit s tokens = print $ splitRecursive tokens s splitRecursive :: [String] -> String -> [String] splitRecursive tokens s = splitOneOf tokens s splitOneOf :: [String] -> String -> [String] splitOneOf [] s = [] splitOneOf (t:tokens) s = map (splitOneOf tokens)(map (T.unpack) (T.splitOn (T.pack t) (T.pack s))) ++ (splitOneOf tokens s) which errors out with: Couldn't match type `[Char]' with `Char' Expected type: String -> String Actual type: String -> [String] In the return type of a call of `splitOneOf' In the first argument of `map', namely `(splitOneOf tokens)' In the first argument of `(++)', namely `map (splitOneOf tokens) (map (T.unpack) (T.splitOn (T.pack t) (T.pack s)))' Failed, modules loaded: none. If anyone has any ideas, that would be awesome! And yes, I'm aware of Data.List.Split, like I said, trying to roll my own....

You map something that returns [String] over a [String] and you get back [[String]], but your function returns [String]. Keep in mind that Strings are Lists of Chars, so ghc is a little confused about what you intended.
:t map (splitOneOf undefined) map (splitOneOf undefined) :: [String] -> [[String]]
Just to make things easier, first thing I'd do is take the spliton stuff
and put it in its own function. Since all it is is a T.splitOn but for
strings, we'll just do that:
sSplitOn :: String -> String -> [String]
sSplitOn t s = map (T.unpack) ((T.pack t) `T.splitOn` (T.pack s))
And then I guessed at what you wanted out of this function, that is to run
splitOn on each item? It seems like you would have gotten it if this was
what you wanted, but it's all I could figure out. I'm probably wrong, but
in case this is what you wanted here it is.
splitOneOf :: [String] -> String -> [String]
splitOneOf [] s = []
splitOneOf (t:tokens) s = (sSplitOn t s) ++ splitOneOf tokens s
If this wasn't what you were looking for, it would help to have some
examples of input and output.
On Thu, Mar 27, 2014 at 12:41 AM, abraham polishchuk
I am relatively new to Haskell, having spent the last half a decade or so developing in Ruby. I am attempting to (for the sake of exercise) implement a split function from the ground up in Haskell, and for the life of me I can not figure out why it doesn't work. Without further ado:
module MyAwesomeModule where
import qualified Data.Text as T
outputSplit :: String -> [String] -> IO () outputSplit s tokens = print $ splitRecursive tokens s
splitRecursive :: [String] -> String -> [String] splitRecursive tokens s = splitOneOf tokens s
splitOneOf :: [String] -> String -> [String] splitOneOf [] s = [] splitOneOf (t:tokens) s = map (splitOneOf tokens)(map (T.unpack) (T.splitOn (T.pack t) (T.pack s))) ++ (splitOneOf tokens s)
which errors out with: Couldn't match type `[Char]' with `Char' Expected type: String -> String Actual type: String -> [String] In the return type of a call of `splitOneOf' In the first argument of `map', namely `(splitOneOf tokens)' In the first argument of `(++)', namely `map (splitOneOf tokens) (map (T.unpack) (T.splitOn (T.pack t) (T.pack s)))' Failed, modules loaded: none.
If anyone has any ideas, that would be awesome! And yes, I'm aware of Data.List.Split, like I said, trying to roll my own....
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (2)
-
abraham polishchuk
-
David McBride