Newbie question on Haskell type

Hi all, I want to write a small functionto test whether an input is a String or not. For example, isString::(Show a) =>a ->Bool This function will return True if the input is a string and return False if not Any of you have idea about that? Thanks in advance

isString::(Show a) =>a ->Bool This function will return True if the input is a string and return False if not This is not particularly nicely - you certainly can't write it as simple as the 'isString' function, and it will probably require type classes etc, quite possibly with haskell extensions. Since haskell is a statically typed langauge the idea is that you know if something is a string before you run the program, not only at runtime.
Why is it you want this? Perhaps what you are hoping to accomplish could be done some other way, without requiring this isString function. Of course, if you want a slightly hacky version: isString x = not (null a) && head a == '\"' && last a == '\"' where a = show x is probably good enough :) Thanks Neil

There is a way to do this using a bunch of GHC extensions, but I get
the feeling that you're misinterpreting parametric polymorphism.
The type (Show a) => a -> Bool means that the function isString can be
implemented without caring what type a is, only knowing that it is in
Show.
As an example of this sort of thing, I know that there are only 4
values of type a -> Bool (without the class context). They are the
constant functions (\x -> True), (\x -> False), and two kinds of
failure (\x -> _|_), and _|_, where _|_ is pronounced "bottom" and
represents something along the lines of nontermination (aborting the
program also counts).
That said, typeclasses, along with undecidable, overlapping instances
(two GHC extensions) will allow us to do this, and without the Show
context, but with an additional context of our own, which every type
happens to be a member of:
class IsString t where
isString :: t -> Bool
instance IsString [Char] where
isString _ = True
instance IsString a where
isString _ = False
Note that you need the command line options -fglasgow-exts,
-fallow-overlapping-instances, and -fallow-undecidable-instances in
order for this to work. Also, the types of things you pass to isString
have to be completely determined. Typing "isString 5" on the ghci
prompt will fail, because ghc will not be able to exactly tell which
type "5" is without context, which it needs to in order to determine
which instance of "isString" applies. Note that if you made String an
instance of Num, then 5 might really represent a string, and the
situation would be completely ambiguous. Typing isString (5 ::
Integer) will work, and return False.
Now here's another question: why do you want it? I can't imagine a
reasonable use of this function which wouldn't be better handled in
some other way. In fact, the only place I've seen this desire before
is in deciding whether to apply putStrLn or print to a value such that
no quotation marks are printed. In that case, you should seriously be
sure that you can't tell the difference between these statically.
Normally in code, where you are prepared to type putStrLn or print,
you know the type that's involved, and it only takes half a second to
think about which of the two to apply. Sometimes you genuinely want to
print a string rather than using putStrLn, as it converts nonprinting
characters into escapes, and clearly shows whether there are spaces at
the end of the string, for instance.
- Cale
On 13/10/05, Huong Nguyen
Hi all,
I want to write a small functionto test whether an input is a String or not. For example,
isString::(Show a) =>a ->Bool This function will return True if the input is a string and return False if not
Any of you have idea about that? Thanks in advance _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Cale Gibbard wrote:
As an example of this sort of thing, I know that there are only 4 values of type a -> Bool (without the class context). They are the constant functions (\x -> True), (\x -> False), and two kinds of failure (\x -> _|_), and _|_, where _|_ is pronounced "bottom" and represents something along the lines of nontermination (aborting the program also counts).
Don't forget (\x -> x `seq` True) and (\x -> x `seq` False). -- Ben

In GHC you can do this:
import Data.Typeable
isString :: (Typeable a) => a -> Bool isString x = typeOf x == typeOf (undefined::String)
Why do you want this? It's not the kind of operation one does very often in Haskell. Huong Nguyen wrote:
Hi all,
I want to write a small functionto test whether an input is a String or not. For example,
isString::(Show a) =>a ->Bool This function will return True if the input is a string and return False if not
Any of you have idea about that? Thanks in advance
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 10/13/05, Huong Nguyen
Hi all,
I want to write a small functionto test whether an input is a String or not. For example,
isString::(Show a) =>a ->Bool This function will return True if the input is a string and return False if not
Any of you have idea about that? Thanks in advance
I simply can not think of a reason for why you would want to do that. The system already knows whether a values if of type String at *compile-time* so there shouldn't really be any reason to test it at run-time. I think you'll get more insight if you just tell us why you think you need it and then we could probably show you the "idiomatic haskell way" to achieve what you need. /S -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

Hi Huong, attached you find a small program for parsing values of various (data) types. It uses a generalized algebraic data type for representing types and a universal data type for representing values. The parser itself is rather simple-minded: it builds on Haskell's "ReadS" type. I don't know whether this is what you are after, but it was fun writing. There are many opportunities for improvement: one could use a decent combinator library for parsing; a type of dynamic values instead of a universal type etc. Here are some example calls: Main> parseAny "4711" [(ValInt 4711,"")] Main> parseAny "\"4711\"" [(ValString "4711","")] Main> parseAny "[4711, 0]" [(ValList [ValInt 4711,ValInt 0],"")] Main> parseAny "[4711, 'a']" [(ValList [ValInt 4711,ValChar 'a'],"")] Main> parseAny "[\"hello world\"]" [(ValList [ValString "hello world"],"")] Note that "parseAny" even parses heterogenous lists. Cheers, Ralf ---
{-# OPTIONS -fglasgow-exts #-}
data Type :: * -> * where Char :: Type Char Int :: Type Int List :: Type a -> Type [a] Value :: Type Value
string :: Type String string = List Char
parse :: Type t -> ReadS t parse (Char) = reads parse (Int) = reads parse (List Char) = reads parse (List a) = parseList (parse (a)) parse (Value) = parseAny
data Value = ValChar Char | ValInt Int | ValString String | ValList [Value] deriving (Show)
parseAny = ValChar <$> parse Char <+> ValInt <$> parse Int <+> ValString <$> parse string <+> ValList <$> parse (List Value)
Helper functions.
parseList parsea = readParen False (\ s -> [ xs | ("[", t) <- lex s, xs <- parsel t ]) where parsel s = [ ([], t) | ("]", t) <- lex s ] ++ [ (x : xs, u) | (x, t) <- parsea s, (xs, u) <- parsel' t ] parsel' s = [ ([], t) | ("]", t) <- lex s ] ++ [ (x : xs, v) | (",", t) <- lex s, (x, u) <- parsea t, (xs, v) <- parsel' u]
infix 8 <$> infixr 6 <+> (f <$> p) s = [ (f a, t) | (a, t) <- p s ] (p <+> q) s = p s ++ q s

Thanks all of your for your time and your interesting examples. Now I can
see that my problem is parsing a String. I am new in Haskell, so, I start to
study parsing and how to create a parser from beginning.
I start with an example from the book as follows:
%The parser item fails if the input is empty and consumes the first
character otherwise.
\begin{code}
newtype Parser a = Parser(String -> [(a, String)])
item::Parser Char
item = Parser(\cs -> case cs of
"" -> []
(c:cs) -> [(c,cs)])
parse :: Parser a -> String -> [(a, String)]
parse p cs = p cs
\end{code}
and I compile, the error displays. I do not know how to fix it. Please help
me.
$ghci parser.lhs
parser.lhs:10:13:
Couldn't match `Parser a' against `t -> t1'
Expected type: Parser a
Inferred type: t -> t1
Probable cause: `p' is applied to too many arguments in the call (p cs)
In the definition of `parse': parse p cs = p cs
Failed, modules loaded: none.
On 10/14/05, Ralf Hinze
Hi Huong,
attached you find a small program for parsing values of various (data) types. It uses a generalized algebraic data type for representing types and a universal data type for representing values. The parser itself is rather simple-minded: it builds on Haskell's "ReadS" type.
I don't know whether this is what you are after, but it was fun writing. There are many opportunities for improvement: one could use a decent combinator library for parsing; a type of dynamic values instead of a universal type etc.
Here are some example calls:
Main> parseAny "4711" [(ValInt 4711,"")] Main> parseAny "\"4711\"" [(ValString "4711","")] Main> parseAny "[4711, 0]" [(ValList [ValInt 4711,ValInt 0],"")] Main> parseAny "[4711, 'a']" [(ValList [ValInt 4711,ValChar 'a'],"")] Main> parseAny "[\"hello world\"]" [(ValList [ValString "hello world"],"")]
Note that "parseAny" even parses heterogenous lists.
Cheers, Ralf
---
{-# OPTIONS -fglasgow-exts #-}
data Type :: * -> * where Char :: Type Char Int :: Type Int List :: Type a -> Type [a] Value :: Type Value
string :: Type String string = List Char
parse :: Type t -> ReadS t parse (Char) = reads parse (Int) = reads parse (List Char) = reads parse (List a) = parseList (parse (a)) parse (Value) = parseAny
data Value = ValChar Char | ValInt Int | ValString String | ValList [Value] deriving (Show)
parseAny = ValChar <$> parse Char <+> ValInt <$> parse Int <+> ValString <$> parse string <+> ValList <$> parse (List Value)
Helper functions.
parseList parsea = readParen False (\ s -> [ xs | ("[", t) <- lex s, xs <- parsel t ]) where parsel s = [ ([], t) | ("]", t) <- lex s ] ++ [ (x : xs, u) | (x, t) <- parsea s, (xs, u) <- parsel' t ] parsel' s = [ ([], t) | ("]", t) <- lex s ] ++ [ (x : xs, v) | (",", t) <- lex s, (x, u) <- parsea t, (xs, v) <- parsel' u]
infix 8 <$> infixr 6 <+> (f <$> p) s = [ (f a, t) | (a, t) <- p s ] (p <+> q) s = p s ++ q s
participants (8)
-
Albert Lai
-
Ben Rudiak-Gould
-
Cale Gibbard
-
Huong Nguyen
-
Neil Mitchell
-
Ralf Hinze
-
robert dockins
-
Sebastian Sylvan