How far does "try" back track? - haskell

So ... I messed up a recording in CSV format:
23,95489,0,20,9888
Due to language settings floating point numbers were written with commas as seperator ... in a comma separated value file ...
Problem is that the file does not have a nice formatting for every float. Some have no point at all and the number of numbers behind the point varies too.
My idea was to build a MegaParsec parser that would try to read every possible floating point formatting, move on and if back track if it finds an error.
Eg for the example above:
read 23,95489 -> good
read 0,20 -> good (so far)
read 9888 -> error (because value is too high for column (checked by guard))
(back tracking to 2.) read 0 -> good again
read 20,9888 -> good
done
I've implemented that as (pseudo code here):
floatP = try pointyFloatP <|> unpointyFloatP
lineP = (,,) <$> floatP <* comma <*> floatP <* comma <*> floatP <* comma
My problem is that apparently the try only works in the 'current' float. There is no backtracking to previous positions. Is this correct?
And if so ... how would I go about implementing further back tracking?

How far does “try” back track?
The parser try p consumes exactly as much input as p if p parses successfully, otherwise it does not consume any input at all. So if you look at that in terms of backtracking, it backtracks to the point where you were when you invoked it.
My problem is that apparently the try only works in the 'current' float. There is no backtracking to previous positions. Is this correct?
Yes, try does not "unconsume" input. All it does is to recover from a failure in the parser you give it without consuming any input. It does not undo the effects of any parsers that you've applied previously, nor does it affect subsequent parsers that you apply after try p succeeded.
And if so ... how would I go about implementing further back tracking?
Basically what you want is to not only know whether pointyFloatP succeeds on the current input, but also whether the rest of your lineP would succeed after successfully pointyFloatP - and if it doesn't you want to backtrack back to before you applied pointyFloatP. So basically you want the parser for the whole remaining line in the try, not just the float parser.
To achieve that you can make floatP take the parser for the remaining line as an argument like this:
floatP restP = try (pointyFloatP <*> restP) <|> unpointyFloatP <*> restP
Note that this kind of backtracking isn't going to be very efficient (but I assume you knew that going in).

Update: Include a custom monadic parser for more complex rows.
Using the List Monad for Simple Parsing
The list monad makes a better backtracking "parser" than Megaparsec. For example, to parse the cells:
row :: [String]
row = ["23", "95489", "0", "20", "9888"]
into exactly three columns of values satisfying a particular bound (e.g., less than 30), you can generate all possible parses with:
{-# OPTIONS_GHC -Wall #-}
import Control.Monad
import Control.Applicative
rowResults :: [String] -> [[Double]]
rowResults = cols 3
where cols :: Int -> [String] -> [[Double]]
cols 0 [] = pure [] -- good, finished on time
cols 0 _ = empty -- bad, didn't use all the data
-- otherwise, parse exactly #n# columns from cells #xs#
cols n xs = do
-- form #d# from one or two cells
(d, ys) <- num1 xs <|> num2 xs
-- only accept #d < 30#
guard $ d < 30
ds <- cols (n-1) ys
return $ d : ds
-- read number from a single cell
num1 (x:xs) | ok1 x = pure (read x, xs)
num1 _ = empty
-- read number from two cells
num2 (x:y:zs) | ok1 x && ok2 y = pure (read (x ++ "." ++ y), zs)
num2 _ = empty
-- first cell: "0" is okay, but otherwise can't start with "0"
ok1 "0" = True
ok1 (c:_) | c /= '0' = True
ok1 _ = False
-- second cell: can't end with "0" (or *be* "0")
ok2 xs = last xs /= '0'
The above list-based parser tries to reduce ambiguity by assuming that if "xxx,yyy" is a number, the "xxx" won't start with zeros (unless it's just "0"), and the "yyy" won't end with a zero (or, for that matter, be a single "0"). If this isn't right, just modify ok1 and ok2 as appropriate.
Applied to row, this gives the single unambiguous parse:
> rowResults row
[[23.95489,0.0,20.9888]]
Applied to an ambiguous row, it gives all parses:
> rowResults ["0", "12", "5", "0", "8601"]
[[0.0,12.5,0.8601],[0.0,12.5,0.8601],[0.12,5.0,0.8601]]
Anyway, I'd suggest using a standard CSV parser to parse your file into a matrix of String cells like so:
dat :: [[String]]
dat = [ ["23", "95489", "0", "20", "9888"]
, ["0", "12", "5", "0", "8601"]
, ["23", "2611", "2", "233", "14", "422"]
]
and then use rowResults above get the row numbers of rows that were ambiguous:
> map fst . filter ((>1) . snd) . zip [1..] . map (length . rowResults) $ dat
[2]
>
or unparsable:
> map fst . filter ((==0) . snd) . zip [1..] . map (length . rowResults) $ dat
[]
>
Assuming there are no unparsable rows, you can regenerate one possible fixed file, even if some rows are ambiguous, but just grabbing the first successful parse for each row:
> putStr $ unlines . map (intercalate "," . map show . head . rowResults) $ dat
23.95489,0.0,20.9888
0.0,12.5,0.8601
23.2611,2.233,14.422
>
Using a Custom Monad based on the List Monad for More Complex Parsing
For more complex parsing, for example if you wanted to parse a row like:
type Stream = [String]
row0 :: Stream
row0 = ["Apple", "15", "1", "5016", "2", "5", "3", "1801", "11/13/2018", "X101"]
with a mixture of strings and numbers, it's actually not that difficult to write a monadic parser, based on the list monad, that generates all possible parses.
The key idea is to define a parser as a function that takes a stream and generates a list of possible parses, with each possible parse represented as a tuple of the object successfully parsed from the beginning of the stream paired with the remainder of the stream. Wrapped in a newtype, our parallel parser would look like:
newtype PParser a = PParser (Stream -> [(a, Stream)]) deriving (Functor)
Note the similarity to the type ReadS from Text.ParserCombinators.ReadP, which is also technically an "all possible parses" parser (though you usually only expect one, unambiguous parse back from a reads call):
type ReadS a = String -> [(a, String)]
Anyway, we can define a Monad instance for PParser like so:
instance Applicative PParser where
pure x = PParser (\s -> [(x, s)])
(<*>) = ap
instance Monad PParser where
PParser p >>= f = PParser $ \s1 -> do -- in list monad
(x, s2) <- p s1
let PParser q = f x
(y, s3) <- q s2
return (y, s3)
There's nothing too tricky here: pure x returns a single possible parse, namely the result x with an unchanged stream s, while p >>= f applies the first parser p to generate a list of possible parses, takes them one by one within the list monad to calculate the next parser q to use (which, as per usual for a monadic operation, can depend on the result of the first parse), and generates a list of possible final parses that are returned.
The Alternative and MonadPlus instances are pretty straightforward -- they just lift emptiness and alternation from the list monad:
instance Alternative PParser where
empty = PParser (const empty)
PParser p <|> PParser q = PParser $ \s -> p s <|> q s
instance MonadPlus PParser where
To run our parser, we have:
parse :: PParser a -> Stream -> [a]
parse (PParser p) s = map fst (p s)
and now we can introduce primitives:
-- read a token as-is
token :: PParser String
token = PParser $ \s -> case s of
(x:xs) -> pure (x, xs)
_ -> empty
-- require an end of stream
eof :: PParser ()
eof = PParser $ \s -> case s of
[] -> pure ((), s)
_ -> empty
and combinators:
-- combinator to convert a String to any readable type
convert :: (Read a) => PParser String -> PParser a
convert (PParser p) = PParser $ \s1 -> do
(x, s2) <- p s1 -- for each possible String
(y, "") <- reads x -- get each possible full read
-- (normally only one)
return (y, s2)
and parsers for various "terms" in our CSV row:
-- read a string from a single cell
str :: PParser String
str = token
-- read an integer (any size) from a single cell
int :: PParser Int
int = convert (mfilter ok1 token)
-- read a double from one or two cells
dbl :: PParser Double
dbl = dbl1 <|> dbl2
where dbl1 = convert (mfilter ok1 token)
dbl2 = convert $ do
t1 <- mfilter ok1 token
t2 <- mfilter ok2 token
return $ t1 ++ "." ++ t2
-- read a double that's < 30
dbl30 :: PParser Double
dbl30 = do
x <- dbl
guard $ x < 30
return x
-- rules for first cell of numbers:
-- "0" is okay, but otherwise can't start with "0"
ok1 :: String -> Bool
ok1 "0" = True
ok1 (c:_) | c /= '0' = True
ok1 _ = False
-- rules for second cell of numbers:
-- can't be "0" or end in "0"
ok2 :: String -> Bool
ok2 xs = last xs /= '0'
Then, for a particular row schema, we can write a row parser as we normally would with a monadic parser:
-- a row
data Row = Row String Int Double Double Double
Int String String deriving (Show)
rowResults :: PParser Row
rowResults = Row <$> str <*> int <*> dbl30 <*> dbl30 <*> dbl30
<*> int <*> str <*> str <* eof
and get all possible parses:
> parse rowResults row0
[Row "Apple" 15 1.5016 2.0 5.3 1801 "11/13/2018" "X101"
,Row "Apple" 15 1.5016 2.5 3.0 1801 "11/13/2018" "X101"]
>
The full program is:
{-# LANGUAGE DeriveFunctor #-}
{-# OPTIONS_GHC -Wall #-}
import Control.Monad
import Control.Applicative
type Stream = [String]
newtype PParser a = PParser (Stream -> [(a, Stream)]) deriving (Functor)
instance Applicative PParser where
pure x = PParser (\s -> [(x, s)])
(<*>) = ap
instance Monad PParser where
PParser p >>= f = PParser $ \s1 -> do -- in list monad
(x, s2) <- p s1
let PParser q = f x
(y, s3) <- q s2
return (y, s3)
instance Alternative PParser where
empty = PParser (const empty)
PParser p <|> PParser q = PParser $ \s -> p s <|> q s
instance MonadPlus PParser where
parse :: PParser a -> Stream -> [a]
parse (PParser p) s = map fst (p s)
-- read a token as-is
token :: PParser String
token = PParser $ \s -> case s of
(x:xs) -> pure (x, xs)
_ -> empty
-- require an end of stream
eof :: PParser ()
eof = PParser $ \s -> case s of
[] -> pure ((), s)
_ -> empty
-- combinator to convert a String to any readable type
convert :: (Read a) => PParser String -> PParser a
convert (PParser p) = PParser $ \s1 -> do
(x, s2) <- p s1 -- for each possible String
(y, "") <- reads x -- get each possible full read
-- (normally only one)
return (y, s2)
-- read a string from a single cell
str :: PParser String
str = token
-- read an integer (any size) from a single cell
int :: PParser Int
int = convert (mfilter ok1 token)
-- read a double from one or two cells
dbl :: PParser Double
dbl = dbl1 <|> dbl2
where dbl1 = convert (mfilter ok1 token)
dbl2 = convert $ do
t1 <- mfilter ok1 token
t2 <- mfilter ok2 token
return $ t1 ++ "." ++ t2
-- read a double that's < 30
dbl30 :: PParser Double
dbl30 = do
x <- dbl
guard $ x < 30
return x
-- rules for first cell of numbers:
-- "0" is okay, but otherwise can't start with "0"
ok1 :: String -> Bool
ok1 "0" = True
ok1 (c:_) | c /= '0' = True
ok1 _ = False
-- rules for second cell of numbers:
-- can't be "0" or end in "0"
ok2 :: String -> Bool
ok2 xs = last xs /= '0'
-- a row
data Row = Row String Int Double Double Double
Int String String deriving (Show)
rowResults :: PParser Row
rowResults = Row <$> str <*> int <*> dbl30 <*> dbl30 <*> dbl30
<*> int <*> str <*> str <* eof
row0 :: Stream
row0 = ["Apple", "15", "1", "5016", "2", "5", "3", "1801", "11/13/2018", "X101"]
main = print $ parse rowResults row0
Off-the-shelf Solutions
I find it a little surprising I can't find an existing parser library out there that provides this kind of "all possible parses" parser. The stuff in Text.ParserCombinators.ReadP takes the right approach, but it assumes that you're parsing characters from a String rather than arbitrary tokens from some other stream (in our case, Strings from a [String]).
Maybe someone else can point out an off-the-shelf solution that would save you from having to role your own parser type, instances, and primitives.

Related

Monadic Parser - handling string with one character

I was reading this Monadic Parsing article while I was trying to implement a pretty simple string parser in Haskell and also get a better understanding of using monads. Down below you can see my code, implementing functions for matching a single character or a whole string. It works as expected, but I observed two strange behaviors that I can't explain.
I have to handle single characters in string, otherwise, the parser will return only empty lists. To be exact, if I remove this line string [c] = do char c; return [c] it won't work anymore. I was expecting that string (c:s) would handle string (c:[]) properly. What could be the cause here?
In my opinion, string definition should be equivalent to string s = mapM char s as it would create a list of [Parser Char] for each character in s and collect the results as Parser [Char]. If I use the definition based on mapM, the program would get stuck in an infinite loop and won't print anything. Is something about lazy evalutation that I miss here?
.
module Main where
newtype Parser a = Parser { apply :: String->[(a, String)] }
instance Monad Parser where
return a = Parser $ \s -> [(a, s)]
ma >>= k = Parser $ \s -> concat [apply (k a) s' | (a, s') <- apply ma s]
instance Applicative Parser where
pure = return
mf <*> ma = do { f <- mf; f <$> ma; }
instance Functor Parser where
fmap f ma = f <$> ma
empty :: Parser a
empty = Parser $ const []
anychar :: Parser Char
anychar = Parser f where
f [] = []
f (c:s) = [(c, s)]
satisfy :: (Char -> Bool) -> Parser Char
satisfy prop = do
c <- anychar
if prop c then return c
else empty
char :: Char -> Parser Char
char c = satisfy (== c)
string :: String -> Parser String
string [] = empty
string [c] = do char c; return [c] --- if I remove this line, all results will be []
string (c:s) = do char c; string s; return (c:s)
main = do
let s = "12345"
print $ apply (string "123") s
print $ apply (string "12") s
print $ apply (string "1") s
print $ apply (string []) s
PS. I think the title of the question is not suggestive enough, please propose an edit if you have a better idea.
Since you did string [] = empty instead of string [] = return [], you can't use it as a base case for recursion that builds up a list.
fmap f ma = f <$> ma is wrong, since <$> is defined in terms of fmap. If you want to define fmap in terms of your other instances, then do fmap = liftA or fmap = liftM. Since mapM uses fmap internally but your original string didn't, this problem didn't come up in your first simple test.
string [] = empty
means: "If you need to parse an empty string, fail -- it can not be parsed at all, no matter what's the input string".
By comparison,
string [] = return ""
means: "If you need to parse an empty string, succeed and return the empty string -- it can always be parsed, no matter what's the input string".
By using the first equation, when you recurse in the case string (c:cs) you need to stop at one character (string [c]) since reaching zero characters will run empty and make the whole parser fail.
Hence, you need to either use that string [c] = return [c] equation, or modify the base "empty string" case so that it succeeds. Arguably, the latter would be more natural.

What is the difference between `readMay` and `readMaybe`?

The two functions readMay and readMaybe have the same signature Read a => String -> Maybe a.
Is there any difference between them? If so, what are they? Which of the two function should be preferred?
There is no difference. Here's how readMay's defined:
-- | This function provides a more precise error message than 'readEither' from 'base'.
readEitherSafe :: Read a => String -> Either String a
readEitherSafe s = case [x | (x,t) <- reads s, ("","") <- lex t] of
[x] -> Right x
[] -> Left $ "no parse on " ++ prefix
_ -> Left $ "ambiguous parse on " ++ prefix
where
maxLength = 15
prefix = '\"' : a ++ if length s <= maxLength then b ++ "\"" else "...\""
where (a,b) = splitAt (maxLength - 3) s
readMay :: Read a => String -> Maybe a
readMay = eitherToMaybe . readEitherSafe
And here is readMaybe:
-- | Parse a string using the 'Read' instance.
-- Succeeds if there is exactly one valid result.
-- A 'Left' value indicates a parse error.
--
-- #since 4.6.0.0
readEither :: Read a => String -> Either String a
readEither s =
case [ x | (x,"") <- readPrec_to_S read' minPrec s ] of
[x] -> Right x
[] -> Left "Prelude.read: no parse"
_ -> Left "Prelude.read: ambiguous parse"
where
read' =
do x <- readPrec
lift P.skipSpaces
return x
-- | Parse a string using the 'Read' instance.
-- Succeeds if there is exactly one valid result.
--
-- #since 4.6.0.0
readMaybe :: Read a => String -> Maybe a
readMaybe s = case readEither s of
Left _ -> Nothing
Right a -> Just a
They differ in the intermediate error message (readEitherSafe shows the input), but the result will be same.
readMay from Safe predates readMaybe from Text.Read. Unless you're on a base version less than 4.6.0.0, use readMaybe from Text.Read as it does not need another package.

Read of types sum

When I want to read string to type A I write read str::A. Consider, I want to have generic function which can read string to different types, so I want to write something like read str::A|||B|||C or something similar. The only thing I could think of is:
{-# LANGUAGE TypeOperators #-}
infixr 9 |||
data a ||| b = A a|B b deriving Show
-- OR THIS:
-- data a ||| b = N | A a (a ||| b) | B b (a ||| b) deriving (Data, Show)
instance (Read a, Read b) => Read (a ||| b) where
readPrec = parens $ do
a <- (A <$> readPrec) <|> (B <$> readPrec)
-- OR:
-- a <- (flip A N <$> readPrec) <|> (flip B N <$> readPrec)
return a
And if I want to read something:
> read "'a'"::Int|||Char|||String
B (A 'a')
But what to do with such weird type? I want to fold it to Int or to Char or to String... Or to something another but "atomic" (scalar/simple). Final goal is to read strings like "1,'a'" to list-like [D 1, D 'a']. And main constraint here is that structure is flexible, so string can be "1, 'a'" or "'a', 1" or "\"xxx\", 1, 2, 'a'". I know how to read something separated with delimiter, but this something should be passed as type, not as sum of types like C Char|I Int|S String|etc. Is it possible? Or no way to accomplish it without sum of types?
There’s no way to do this in general using read, because the same input string might parse correctly to more than one of the valid types. You could, however, do this with a function like Text.Read.readMaybe, which returns Nothing on ambiguous input. You might also return a tuple or list of the valid interpretations, or have a rule for which order to attempt to parse the types in, such as: attempt to parse each type in the order they were declared.
Here’s some example code, as proof of concept:
import Data.Maybe (catMaybes, fromJust, isJust, isNothing)
import qualified Text.Read
data AnyOf3 a b c = FirstOf3 a | SecondOf3 b | ThirdOf3 c
instance (Show a, Show b, Show c) => Show (AnyOf3 a b c) where
show (FirstOf3 x) = show x -- Can infer the type from the pattern guard.
show (SecondOf3 x) = show x
show (ThirdOf3 x) = show x
main :: IO ()
main =
(putStrLn . unwords . map show . catMaybes . map readDBS)
["True", "2", "\"foo\"", "bar"] >>
(putStrLn . unwords . map show . readIID) "100"
readMaybe' :: (Read a, Read b, Read c) => String -> Maybe (AnyOf3 a b c)
-- Based on the function from Text.Read
readMaybe' x | isJust a && isNothing b && isNothing c =
(Just . FirstOf3 . fromJust) a -- Can infer the type of a from this.
| isNothing a && isJust b && isNothing c =
(Just . SecondOf3 . fromJust) b -- Can infer the type of b from this.
| isNothing a && isNothing b && isJust c =
(Just . ThirdOf3 . fromJust) c -- Can infer the type of c from this.
| otherwise = Nothing
where a = Text.Read.readMaybe x
b = Text.Read.readMaybe x
c = Text.Read.readMaybe x
readDBS :: String -> Maybe (AnyOf3 Double Bool String)
readDBS = readMaybe'
readToList :: (Read a, Read b, Read c) => String -> [AnyOf3 a b c]
readToList x = repack FirstOf3 x ++ repack SecondOf3 x ++ repack ThirdOf3 x
where repack constructor y | isJust z = [(constructor . fromJust) z]
| otherwise = []
where z = Text.Read.readMaybe y
readIID :: String -> [AnyOf3 Int Integer Double]
readIID = readToList
The first output line echoes every input that parsed successfully, that is, the Boolean constant, the number and the quoted string, but not bar. The second output line echoes every possible interpretation of the input, that is, 100 as an Int, an Integer and a Double.
For something more complicated, you want to write a parser. Haskell has some very good libraries to build them out of combinators. You might look at one such as Parsec. But it’s still helpful to understand what goes on under the hood.

Getting an integer from the console

Is there a way to read an integer from the console in Haskell? I'm asking for something pretty much like C++'s cin or Java's Scanner.nextInt().
And by that I mean that given this input:
1 2 3
2 3
4 25 12 7
1
I should be able to read them all, not at the same time (maybe reading 4 of them, doing some calculations and then read the rest) ignoring the fact that they are in separate lines.
The easiest solution is probably
getAll :: Read a => IO [a]
getAll = fmap (fmap read . words) getContents
getInts :: IO [Int]
getInts = getAll
which will read all input into a single list.
When in doubt, use Parsec! (not always, and not really, but who cares)
import Text.ParserCombinators.Parsec
import Text.Parsec.Numbers
value = do
spaces
num <- parseFloat
return num
line = many value
then "rinse and repeat", with getLine until you EOF.
Note: you can do it without Parsec using read and friends, but this way is more extendable and preferred for more complicated grammars.
Using Parsec:
import Text.ParserCombinators.Parsec
import Text.Parsec.Numbers
import Control.Applicative ((*>), (<*))
line = spaces *> many1 (parseFloat <* spaces)
main = putStrLn "Enter numbers:" >> fmap (parse line "") getLine >>= print
Running it:
$ ghc parsenums.hs
$ ./parsenums
Enter numbers:
345 23 654 234
[345.0,23.0,654.0,234.0]
A more "manual" way to do it would be something like:
import Data.Char (isDigit, isSpace)
getInts :: String -> [Int]
getInts s = case span isDigit (dropWhile isSpace s) of
("", "") -> []
("", s) -> error $ "Invalid input: " ++ s
(digits, rest) -> (read digits :: Int) : getInts rest
Which might be much clearer to see how it works. In fact, here's one that's completely from the ground up:
getInts :: String -> [Int]
getInts s = case span isDigit (dropWhile isSpace s) of
("", "") -> []
("", s) -> error $ "Invalid input: " ++ s
(digits, rest) -> strToInt digits : getInts rest
isDigit :: Char -> Bool
isDigit c = '0' <= c && c <= '9'
isSpace :: Char -> Bool
isSpace c = c `elem` " \t\n\r"
charToInt :: Char -> Int
charToInt c = fromEnum c - 48
strToInt :: String -> Int
strToInt s = go 0 s where
go n [] = n
go n (c:rest) = go (n * 10 + charToInt c) rest

read data from a list of strings

i have a data structure like this
data Something = Something Integer String String
and i want to convert
["Something", "3", "text", "42"]
to the data.
for now, i have
altRead :: Read a => [String] -> a
altRead = read . unwords . hack
where
hack = map (\x -> if isNumber x then x else "\"" ++ x ++ "\"")
isNumber = foldl (\b c -> isDigit c && b) True
but i forgot, that some numbers could be strings in the data structure.
is there a simple solution for this or do i need to write a alternative read typeclass?
You're writing a tiny parser atop some lexed tokens. You can't really implement a Read instance since read :: Read a => String -> a and you want to do [String] -> a for a == Something. You can take advantage of Read instances that already exist, though, to bootstrap parsing your Integer, for instance.
So let's try it. We'll parse a Something from the list of tokens.
import Safe -- gives us readMay :: Read a => String -> Maybe a
parseSomething :: [String] -> Maybe Something
parseSomething ("Something":strInt:stra:strb:_) =
do int <- readMay strInt
return $ Something int stra strb
parseSomething _ = Nothing
We could do it a little more compactly using Maybe as an Applicative, too
import Control.Applicative
parseSomething :: [String] -> Maybe Something
parseSomething ("Something":strInt:stra:strb:_) =
Something <$> readMay strInt <*> pure stra <*> pure strb
parseSomething _ = Nothing
Really, we should probably return any unconsumed tokens as well so we can continue parsing.
parseSomething :: [String] -> (Maybe Something, [String])
parseSomething ("Something":strInt:stra:strb:rest) =
(Something <$> readMay strInt <*> pure stra <*> pure strb, rest)
parseSomething rest = (Nothing, rest)
The reason I bring in all this structure to your parse is that this starts to head toward the space of parser combinators like Parsec. Whenever you've got a need for a complicated Read it begins to become useful to look at some of the really nice parsing libraries in Haskell.
With what you have, you don't really need to make it a typeclass. You can just do:
readSomething :: [String] -> Maybe Something
readSomething [_, n, s1, s2] = Just $ Something (read n) s1 s2
readSomething _ = Nothing
or, if you want to disambiguate on the first word:
data Something = Something Integer String String
| SomethingToo String Integer
readSomething :: [String] -> Maybe Something
readSomething ["Something", n, s1, s2] = Just $ Something (read n) s1 s2
readSomething ["SomethingToo", s, n] = Just $ SomethingToo s (read n)
readSomething _ = Nothing
In GHCI:
data Something = Something Integer String String deriving (Read, Show)
let somethingStrings = ["Something", "3", "text", "42"]
let escapeForSomething [a,b,c,d] = [a, b, "\""++c++"\"", "\""++d++"\""]
let something = read (unwords (escapeForSomething somethingStrings)) :: Something

Resources