Re: [Haskell-cafe] Newbie question on Haskell type

2005-10-16 Thread Huong Nguyen
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 [EMAIL PROTECTED] wrote:

Hi Huong,attached you find a small program for parsing values of various (data)types. It uses a generalized algebraic data type for representing typesand 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 auniversal 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 =ValCharChar |ValInt Int |ValStringString |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 parsels= [ ([], 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] infix8$ infixr 6+ (f $ p) s=[ (f a, t) | (a, t) - p s ] (p + q) s=p s ++ q s

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question on Haskell type

2005-10-16 Thread Albert Lai
Huong Nguyen [EMAIL PROTECTED] writes:

 newtype Parser a = Parser(String - [(a, String)])

[...]

 parse :: Parser a - String - [(a, String)]
 parse p cs = p cs
 \end{code}

Try this instead:

parse (Parser p) cs = p cs

(You forgot to deconstruct! :) )
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question on Haskell type

2005-10-14 Thread Cale Gibbard
Right, forgot about seq there, but the point still holds that there
are a very limited number of functions of that type, and in
particular, the functions can't decide what to do based on the type
parameter 'a'.

 - Cale

On 14 Oct 2005 05:49:27 -, [EMAIL PROTECTED]
[EMAIL PROTECTED] wrote:
 --- Cale Gibbard [EMAIL PROTECTED] 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).

 Not exactly. There are also (\x - seq x True)
 and (\x - seq x False), neither of which is equivalent to any of the four
 functions above.

 Regards,

 Janis Voigtlaender.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question on Haskell type

2005-10-14 Thread John Meacham
On Fri, Oct 14, 2005 at 03:17:12AM -0400, Cale Gibbard wrote:
 Right, forgot about seq there, but the point still holds that there
 are a very limited number of functions of that type, and in
 particular, the functions can't decide what to do based on the type
 parameter 'a'.


actually, without 'seq' _|_ and \_ - _|_ are indistinguishable. so you
only have 3 functions without seq, and 6 with it.

John

--
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question on Haskell type

2005-10-14 Thread Ben Rudiak-Gould

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question on Haskell type

2005-10-14 Thread Sebastian Sylvan
On 10/13/05, Huong Nguyen [EMAIL PROTECTED] 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

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question on Haskell type

2005-10-14 Thread robert dockins
So this is essentially a parsing problem.  You want a user to be able 
input a string and have it interpreted as an appropriate data value.  I 
think you may want to look at the Parsec library 
(http://www.cs.uu.nl/~daan/parsec.html).  I don't think the direction 
you are heading will get the results you want.



As to typeable, the basic types are mostly all members of Typeable.  You 
can find a pretty good list here:


http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.Typeable.html#t%3ATypeable

Additionally, GHC can create Typeable instances automaticly for user 
defined datatypes; just add a deriving Typeable clause.


data SomeType = C1 | C2 deriving (Show,Eq,Typeable)

The restriction is that all types which appear in constructors must also 
be in Typeable.


I believe the DrIFT preprocessor can also create Typeable instances if 
you are not using GHC.


Huong Nguyen wrote:

Hello,

Thanks for your solution.

My main purpose is that I want to input a value and check whether this 
value is belong to some specific types or not. These types can be some 
popular types (such as: String, Char, Int, etc) or some more complex 
data structures defined by user. Thus, at first, I try with type String 
(even with that simple type, I still face difficulty ;-))


I want to ask you which types can be used with Data.Typeable. I read for 
over 15 minutes but it is still not clear with me.
For some other complex data types defined by user, what I should do to 
use Data.Typeable ?


Thank you very much.

On 10/13/05, *robert dockins* [EMAIL PROTECTED] 
mailto:[EMAIL PROTECTED] wrote:


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 mailto:Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question on Haskell type

2005-10-14 Thread 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 
   =  ValCharChar
   |  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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question on Haskell type

2005-10-13 Thread Neil Mitchell
 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question on Haskell type

2005-10-13 Thread robert dockins

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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question on Haskell type

2005-10-13 Thread voigt . 16734551
--- Cale Gibbard [EMAIL PROTECTED] 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).

Not exactly. There are also (\x - seq x True)
and (\x - seq x False), neither of which is equivalent to any of the four
functions above.

Regards,
Janis Voigtlaender.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe