Re: [Haskell-cafe] Newbie Q: Monad 'fail' and 'error'

2007-06-06 Thread Dmitri O.Kondratiev
7;cast' divBy to List, Identity, other monads? How? On 6/6/07, Tillmann Rendel <[EMAIL PROTECTED]> wrote: Dmitri O.Kondratiev wrote: > Monad class contains declaration > > *fail* :: String -> m a > > and provides default implementation for 'fail' as

[Haskell-cafe] Newbie Q: Monad 'fail' and 'error'

2007-06-06 Thread Dmitri O.Kondratiev
Monad class contains declaration *fail* :: String -> m a and provides default implementation for 'fail' as: fail s = error s On the other hand Prelude defines: * error* :: String -> a which stops execution and displays an error message. Questions: 1) What value and type 'error' actually retu

Re: [Haskell-cafe] Newbie: a parser for a list of objects?

2007-03-29 Thread Dmitri O.Kondratiev
(dig <:> (dig <:> succeed []))) ~~> [("123", "")] (dig <:> (dig <:> (dig <:> (dig <:> pList dig ~~> [] the last one returns [] because: (dig >*> dig >*> dig >*> dig) "123" ~~> [] As a result we get: [(&

Re: [Haskell-cafe] Newbie: a parser for a list of objects?

2007-03-28 Thread Dmitri O.Kondratiev
((p >*> pList p) `build` (uncurry (:))) comp1 = dig >*> dig comp2 = dig >*> (succeed []) pl1 = comp2 `build` (uncurry (:)) test = pList dig On 3/28/07, Daniel Fischer <[EMAIL PROTECTED]> wrote: Am Dienstag, 27. März 2007 12:15 schrieb Dmitri O.Kondratiev: > Th

Re: [Haskell-cafe] Newbie: a parser for a list of objects?

2007-03-27 Thread Dmitri O.Kondratiev
List p will be done *before* 'build' will be applied? Correct? Thanks, Dima On 3/26/07, Daniel Fischer <[EMAIL PROTECTED]> wrote: > -Ursprüngliche Nachricht- > Von: "Dmitri O.Kondratiev" <[EMAIL PROTECTED]> > Gesendet: 26.03.07 16:44:12 > An: h

[Haskell-cafe] Newbie: a parser for a list of objects?

2007-03-26 Thread Dmitri O.Kondratiev
Please see my questions inside comments {-- --} : Thanks! --- module Parser where import Data.Char type Parse a b = [a] -> [(b, [a])] {-- Newbie: a parser for a list of objects? I am working with the section 17.5 "Case study: parsing expressions" of the book "Haskell The Craft of Functional

Re: [Haskell-cafe] Newbie: Is 'type' synonym hiding two much?

2007-03-22 Thread Dmitri O.Kondratiev
Now, in the 17.5 section of a book one may see the following declarations: succeed :: b -> Parse a b *Before looking at 'succeed' function definition* one may think that 'succeed' is a function of *one* argument of type 'b' that returns object of type 'Parse a b'. That's what it is. Howev

[Haskell-cafe] Newbie: Is‘type’ synonym h iding two much?

2007-03-22 Thread Dmitri O.Kondratiev
I am learning Haskell working through Simon Thompson book "Haskell The Craft of Functional Programming" (second edition). Solving problems in the book with more or less success I arrived almost to the end of the book at the section 17.5 "Case study: parsing expressions". Most probably the question

Re: [Haskell-cafe] Newbie Q: GHCi: W here “List” module is imported from?

2007-02-16 Thread Dmitri O.Kondratiev
On 2/16/07, Jules Bean <[EMAIL PROTECTED]> wrote: Actually, lists are partly defined in the Prelude, with auxiliary functions in Data.List. In particular, <= for List is defined in the Prelude. Or rather, I should say, the Ord instance for lists is defined in the prelude (and only if the type in

[Haskell-cafe] Newbie Q: GHCi: Where “Lis t” module is imported from?

2007-02-16 Thread Dmitri O.Kondratiev
Going through "Haskell. The Craft of Functional Programming" book , in section 16.8 I found a Set module example. Module declarations starts with: import List hiding (union) "Set" module here is built with list and uses among other things list comparison functions such as (==) and (<=). For exa

Re: [Haskell-cafe] Newbie Q: composeMaybe :: (a -> Maybe b) -> (b -> Maybe c) -> (a -> Maybe c)

2006-11-09 Thread Dmitri O.Kondratiev
ent to f1. (I used different type variables to reduce confusion) This constraint gives f1 the following type f1 :: (c -> Maybe d) -> (t -> Maybe c) -> t -> Maybe (Maybe d) substituting different type variable names gives f1 :: (b -> Maybe c) -> (a -> Maybe b) -> a -&g

[Haskell-cafe] Newbie Q: composeMaybe :: (a -> Maybe b) -> (b -> Maybe c) -> (a -> Maybe c)

2006-11-08 Thread Dmitri O.Kondratiev
I am trying to solve a problem from "The Craft of Functional Programming" book: 14.38 ... define the function: data Maybe a = Nothing | Just a composeMaybe :: (a -> Maybe b) -> (b -> Maybe c) -> (a -> Maybe c) using functions: squashMaybe :: Maybe (Maybe a) -> Maybe a squashMaybe (Just (Just x)

Re: [Haskell-cafe] Newbie Q: Deriving MyOrd from Eq problem

2006-07-26 Thread Dmitri O.Kondratiev
On 7/25/06, Jared Updike <[EMAIL PROTECTED]> wrote: > I am trying to derive MyOrd class from Eq (Prelude): > > class Eq a => MyOrd a where > (%<=), (%>), (%>=) :: a -> a -> Bool > x %<= y = (x < y || x == y) > x %> y = y < x > x %>= y = (y < x || x == y) > > Q: Wh

[Haskell-cafe] Newbie Q: Deriving MyOrd from Eq problem

2006-07-25 Thread Dmitri O.Kondratiev
I am trying to derive MyOrd class from Eq (Prelude): class Eq a => MyOrd a where (%<=), (%>), (%>=) :: a -> a -> Bool x %<= y = (x < y || x == y) x %> y = y < x x %>= y = (y < x || x == y) I get these errors: ClassTest.hs:28:21: Could not deduce (Ord a) from the

Re: [Haskell-cafe] Haskell on Pocket PC?

2006-04-03 Thread Dmitri O.Kondratiev
Hi Neil, Thanks for your reply. Starting from YHC porting pages the only source for Win32 port I found is WinHaskell. [http://www-users.cs.york.ac.uk/~ndm/projects/winhaskell.php] I have not yet found which port it is: Hugs, YHc, ...? Also there is a thing called WinHugs at http://www-users.cs.y

[Haskell-cafe] Re: Haskell on Pocket PC?

2006-03-31 Thread Dmitri O.Kondratiev
I am sorry for confusion that abreviation PPC may cause in the text of my message. In this context I used 'PPC' to refer to Pocket PC and nothing else. Sorry again. On 3/31/06, Dmitri O.Kondratiev <[EMAIL PROTECTED]> wrote: > Any ideas on how much work needs to be done for u

[Haskell-cafe] Haskell on Pocket PC?

2006-03-31 Thread Dmitri O.Kondratiev
Any ideas on how much work needs to be done for using Haskell on PPC Windows Mobile platform? It would be interesting to use PPC as: 1) Haskell learning tool, so small code snipets could be entered and run directly on hand-held (REPL). How hard is it to port Hugs to PPC for this? Do any other (then

<    1   2