Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Haskell and Niches (Jordan Cooper)
   2.  Re: Accounting Engine in Haskell (Heinrich Apfelmus)
   3.  Re: Haskell and Niches (Heinrich Apfelmus)
   4. Re:  Extract and integer from a ByteString (Tom Hobbs)
   5. Re:  Extract and integer from a ByteString (Yitzchak Gale)
   6.  Re: Haskell and Niches (Alain Cremieux)
   7. Re:  Extract and integer from a ByteString (Yitzchak Gale)
   8. Re:  Extract and integer from a ByteString (Stephen Tetley)


----------------------------------------------------------------------

Message: 1
Date: Tue, 15 Jun 2010 20:12:54 -0700
From: Jordan Cooper <nefi...@gmail.com>
Subject: [Haskell-beginners] Haskell and Niches
To: beginners <beginners@haskell.org>
Message-ID:
        <aanlktimgf-1ien98xw5iszaz92ta8eur_r5w1hxgy...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

The recent mailings about using Haskell for an accounting system got
me thinking, since people have pointed out the things that would make
the language suited for the task.

Does this means there are some programming tasks that Haskell is great
for, and others that you would pick a different language for? I was
under the impression that it was more a "general purpose" language
than a "niche" language--I'm using it for programming a decently
ambitious (though small) game now, and it's bending my brain but I
suspect it is fully possible even though games are traditionally
imperatively programmed.

Do you try to use Haskell for every project? Is there some sort of
"right tool for the right job" adage you follow?


------------------------------

Message: 2
Date: Wed, 16 Jun 2010 09:16:14 +0200
From: Heinrich Apfelmus <apfel...@quantentunnel.de>
Subject: [Haskell-beginners] Re: Accounting Engine in Haskell
To: beginners@haskell.org
Cc: haskell-c...@haskell.org
Message-ID: <hv9tnu$21...@dough.gmane.org>
Content-Type: text/plain; charset=UTF-8

Amiruddin Nagri wrote:
> My current project is about making an accounting engine that handles all
> the journal entries, transactions, portfolios etc. The communication
> with the engine is based on simple protocol, the things to be taken
> care of in the order are consistency, handling large data(performance) and
> availability.
> 
> I came across a video lecture by Simon Peyton Jones where he gives an
> example from Financial domain (derivatives etc) to explain how haskell is
> being used and the advantages provided.
> 
> I am interested in knowing if Haskell will be the right fit for my project.
> My requirements are transactional nature, which I believe is one of the
> strengths of functional programming, also handling large data set and being
> available. there is no such requirement for partitioning of data and the
> application is going to be centrally hosted on a single server.

Keep in mind that you have to invest some time in learning Haskell
before you can reap the benefits. For an example of the latter, see also

  Paul Hudak, Mark P. Jones.
  Haskell vs. Ada vs. C++ vs. Awk vs. ...,
    An Experiment in Software Prototyping Productivity
  http://haskell.org/papers/NSWC/jfp.ps

In a sense, you have to learn programming anew.

> AFAIK OCaml and other functional languages are heavily used in financial
> domain, some of the reason are same as features I am looking for.

A key philosophy of Haskell compared to other functional programming
languages like OCaml or Clojure is that Haskell is  pure , i.e.
functions do not have side-effects. Incidentally, purity is the only way
to implement software transactional memory with the proper static
guarantees.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com



------------------------------

Message: 3
Date: Wed, 16 Jun 2010 09:29:53 +0200
From: Heinrich Apfelmus <apfel...@quantentunnel.de>
Subject: [Haskell-beginners] Re: Haskell and Niches
To: beginners@haskell.org
Message-ID: <hv9uhh$4g...@dough.gmane.org>
Content-Type: text/plain; charset=UTF-8

Jordan Cooper wrote:
> The recent mailings about using Haskell for an accounting system got
> me thinking, since people have pointed out the things that would make
> the language suited for the task.
> 
> Does this means there are some programming tasks that Haskell is great
> for, and others that you would pick a different language for? I was
> under the impression that it was more a "general purpose" language
> than a "niche" language--I'm using it for programming a decently
> ambitious (though small) game now, and it's bending my brain but I
> suspect it is fully possible even though games are traditionally
> imperatively programmed.
> 
> Do you try to use Haskell for every project? Is there some sort of
> "right tool for the right job" adage you follow?

I'm using Haskell for everything. This may not mean much because
"everything" is mainly shell scripting and parsing for me.

For example, I wrote a small  make -like DSL in Haskell for my website
because GNUmake grew too cumbersome for me.

Of course, I'm still using short shell scripts for bash commands and
the-like. But my rule of thumb is that I write everything which involves
a for loop in Haskell.

(Unfortunately, I don't use Haskell for GUI scripting which pretty much
requires a particular language (AppleScript).)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com



------------------------------

Message: 4
Date: Wed, 16 Jun 2010 08:40:12 +0100
From: Tom Hobbs <tvho...@googlemail.com>
Subject: Re: [Haskell-beginners] Extract and integer from a ByteString
To: beginners@haskell.org
Message-ID:
        <aanlktimjs1w5tr7noszdhhphul_yehbjo6cpdelsh...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi Stephen,

Thanks for the answer, I shall give it a go later tonight (UK time).

Why would I want to keep my functions monadic?  It's not that I'm against
the idea, rather it's that I don't understand the choice.  I was under the
(possibly wrong) impression that (IO) monadic functions were just to "get
around" the issue of side-effects and that where possible functions should
be coded outside of monads.  Is that just plain wrong, or does it boil down
to "It depends on what you're doing, and in this case..."?

Also I think I've already encountered the hidden Data.Binary problem in GHC.
 I have got around it already by (if memory serves) starting GHC and telling
it to ignore it's own Data.Binary so I can then include it in my own
projects.  But I created an alias which starts this Data.Binary-capable GHC
and I can't remember what's behind it now!

What's the reason for GHC hiding packages and preventing them from being
imported/used in loaded projects?

Thanks again for the help.

Tom

On Tue, Jun 15, 2010 at 9:15 PM, Stephen Tetley <stephen.tet...@gmail.com>wrote:

> Hi Tom
>
> Try ...
>
> extractInt :: [Word8] -> Int
> extractInt = foldl addDigit 0
>               where
>                addDigit num d = 10*num + (fromIntegral d)
>
>
> You might find you want to keep your functions monadic, and mostly use
> the Get monad from the module Data.Binary.Get for working with binary
> data.For instance there is a function getWord32be to do the work that
> extractInt is doing
>
> Best wishes
>
> Stephen
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100616/bd5875f6/attachment-0001.html

------------------------------

Message: 5
Date: Wed, 16 Jun 2010 12:07:06 +0300
From: Yitzchak Gale <g...@sefer.org>
Subject: Re: [Haskell-beginners] Extract and integer from a ByteString
To: Tom Hobbs <tvho...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktikjwewfqabmpg7xu1z616ejixyzwnfv8u4bd...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Tom Hobbs wrote:
> I have a stream of bytes...
> Where the first four bytes tell me the number of bytes I should read next in
> order to get some string value...
>
> What I have is code similar to the following;
>
> readFromStream address port     =
>                do
>                h <- connectTo address (PortNumber port)
>                hSetBuffering h NoBuffering
>                L.hPut h (encode (0xFAB10000 :: Word32))
>                p <- L.hGet h 4
>                readData h (extractInt((L.unpack p)))
>
> extractInt      = foldl addDigit 0
>                where
>                addDigit num d = 10*num + d
>
> readData h c    = do
>                print c
>                s <- L.hGet h c
>                print s

You're looking for the binary package. That is a general
library for encoding and decoding of binary data streams
via lazy bytestrings.

http://hackage.haskell.org/package/binary

Then you can write:

import Data.Binary.Get
...
    n <- fmap (runGet word32be) $ L.hGet h 4
    theString <- L.hGet h n

This gives you theString as a lazy bytestring, of course.
You take it from there.

Regards,
Yitz


------------------------------

Message: 6
Date: Wed, 16 Jun 2010 09:07:16 +0000 (UTC)
From: Alain Cremieux <alcr...@pobox.com>
Subject: [Haskell-beginners] Re: Haskell and Niches
To: beginners@haskell.org
Message-ID: <loom.20100616t110313-...@post.gmane.org>
Content-Type: text/plain; charset=us-ascii

Heinrich Apfelmus <apfelmus <at> quantentunnel.de> writes:

> 
> Jordan Cooper wrote:
> [snip]

> I'm using Haskell for everything. This may not mean much because
> "everything" is mainly shell scripting and parsing for me.
> 
> Of course, I'm still using short shell scripts for bash commands and
> the-like. But my rule of thumb is that I write everything which involves
> a for loop in Haskell.
> 
> Regards,
> Heinrich Apfelmus
> 
> --
> http://apfelmus.nfshost.com
> 
> 


Which haskell library do you use to interact with the OS/bash, and do shell
scripting ?

Thanks,
Alain



------------------------------

Message: 7
Date: Wed, 16 Jun 2010 12:23:11 +0300
From: Yitzchak Gale <g...@sefer.org>
Subject: Re: [Haskell-beginners] Extract and integer from a ByteString
To: Tom Hobbs <tvho...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktimvbzt6ov2fv1rrg7qxjyigall9qwa9iqqng...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

I wrote:
> import Data.Binary.Get
> ...
>    n <- fmap (runGet word32be) $ L.hGet h 4
>    theString <- L.hGet h n

Oops, you also need to convert from Word32 to Int:

  n <- fmap (fromIntegral . runGet word32be) $ L.hGet h 4

Regards,
Yitz


------------------------------

Message: 8
Date: Wed, 16 Jun 2010 11:18:28 +0100
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] Extract and integer from a ByteString
To: Tom Hobbs <tvho...@googlemail.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktil5pbzn08x81qa8u9krmoc94g5kntatpggl7...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On 16 June 2010 08:40, Tom Hobbs <tvho...@googlemail.com> wrote:
> Hi Stephen,
>
> Thanks for the answer, I shall give it a go later tonight (UK time).
> Why would I want to keep my functions monadic?  It's not that I'm against
> the idea, rather it's that I don't understand the choice.  I was under the
> (possibly wrong) impression that (IO) monadic functions were just to "get
> around" the issue of side-effects and that where possible functions should
> be coded outside of monads.  Is that just plain wrong, or does it boil down
> to "It depends on what you're doing, and in this case..."?

Hi Tom


Yes - its a "depend on what your doing" thing...

For reading binary data, having a set of functions to read different
types of data provides a nice interface. Data.Binary.Get provides some
- e.g. getWord8, getWord32,... - and they are all in the Get monad.
For a particular domain you would want to
construct the parsers for that domain - but still keep them in the Get
monad so you would keep the uniform interface.

E.g., say if you had a structure for IP address, stored without the dots:

data IPAddr = IPAddr Word8 Word8 Word8 Word8

getIPAddr :: Get IPAddr
getIPAdde = do
  { a <- getWord8
  ; b <- getWord8
  ; c <- getWord8
  ; d <- getWord8
  ; return (IPAddr a b c d)
  }

In you original code, the extractInt function is a good candidate to
be a "Get" function rather than a a function that turns [Word8] data
into an Int - i.e. I would make it do some parsing work rather than
just the data conversion. As you are always reading 4 bytes and its
big endian (I think?), I would adapt the existing getWord32be parser:

extractInt :: Get Int
extractInt = do
  { a <- getWord32be
  ; return (fromIntegral a)
  }

Or more succinctly:

extractInt :: Get Int
extractInt = liftM fromIntegral getWord32be

liftM, liftM2 are a family of functions that post-process the value
(or values) returned from monadic operation(s) with a pure function
(here fromIntegral).

Of course, this will mean that the other code will have to be changed
to use Data.Binary.Get but the end result should be cleaner code.

> Also I think I've already encountered the hidden Data.Binary problem in GHC.
>  I have got around it already by (if memory serves) starting GHC and telling
> it to ignore it's own Data.Binary so I can then include it in my own
> projects.  But I created an alias which starts this Data.Binary-capable GHC
> and I can't remember what's behind it now!
> What's the reason for GHC hiding packages and preventing them from being
> imported/used in loaded projects?

GHC used to ship with a lot of libraries, but that was a large
maintenance effort and now the Haskell Platform does this job.
However, GHC is self-contained, so it still ships versions of the
third-party libraries it uses internally (base, containers, the
cabal-libraries but not the "cabal install" the tool...). I think
Data.Binary is a more recent dependency, and its perhaps just an
accident that it is half in / half out.

Best wishes

Stephen


------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 24, Issue 17
*****************************************

Reply via email to