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.  Crash Course for C++ "Refugees"? (Frank)
   2. Re:  Crash Course for C++ "Refugees"? (Mark Santolucito)
   3.  State Monad  vs. fold (martin)
   4. Re:  State Monad  vs. fold (John Wiegley)
   5. Re:  Too much mapM, fmap and concat (Vlatko Basic)
   6. Re:  expressing constraints 101 (Dimitri DeFigueiredo)


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

Message: 1
Date: Wed, 13 Aug 2014 13:19:12 -0400
From: Frank <frankdmarti...@gmail.com>
To: beginners@haskell.org
Subject: [Haskell-beginners] Crash Course for C++ "Refugees"?
Message-ID:
        <ca+a3wkjik6bjfma6f0awci5lqghgfidqbmkmv1aydt4uu_h...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi,
    I have recently been introduced to Haskell and find it quite
fascinating. I am interested in incorporating it into a C++ project on
which I am working, porting pieces of that program to Haskell when
practical. Is Anyone able to point Me in the direction of a "crash course"
or "quick start" guide for Anyone used to programming in C++ seeking to
call Haskell code from the C++ portion and/or vice versa? I am especially
interested in knowing how to pass information from, say, the C++ standard
template library containers (e.g., vector, valarray, etc.) and into Haskell
functions/methods/procedures/etc. While I might have missed such
information when I performed a web search on the topic, I did not find any
information to help. Any assistance in finding such material would be
greatly appreciated.

Sincerely,
Frank D. Martinez

-- 
P.S.: I prefer to be reached on BitMessage at
BM-2D8txNiU7b84d2tgqvJQdgBog6A69oDAx6
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20140813/0abcdaac/attachment-0001.html>

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

Message: 2
Date: Wed, 13 Aug 2014 13:40:34 -0400
From: Mark Santolucito <mark.santoluc...@yale.edu>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Crash Course for C++ "Refugees"?
Message-ID:
        <CAFivCSo7vJhvUZBog=fy7okh7csqih6seabffwjbenqsgrj...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi Frank,

You are looking for the foreign function interface (FFI) for Haskell.
Googling this will produce no end of _somewhat_ useful results. Basically
you can call Haskell from C and vice versa. I'm not aware of a hs ffi
explicitly for C++, but it is essentially the same/likely short work to do
the C<->C++ interface for any particular application.

http://www.haskell.org/haskellwiki/FFI_Introduction

http://www.haskell.org/haskellwiki/GHC/Using_the_FFI

There is some code that I wrote for an abandoned project that might help
you out at lotusstem.us/ffi.zip (sorry for the random site, the code
somehow ended up on that server and I'm without a laptop to easily move it
now). If i remember correctly I had issues with hsFFI.h so just avoided
using it entirely. Likely not the correct approach but hopefully enough to
get you started.

Mark
On Aug 13, 2014 1:20 PM, "Frank" <frankdmarti...@gmail.com> wrote:

> Hi,
>     I have recently been introduced to Haskell and find it quite
> fascinating. I am interested in incorporating it into a C++ project on
> which I am working, porting pieces of that program to Haskell when
> practical. Is Anyone able to point Me in the direction of a "crash course"
> or "quick start" guide for Anyone used to programming in C++ seeking to
> call Haskell code from the C++ portion and/or vice versa? I am especially
> interested in knowing how to pass information from, say, the C++ standard
> template library containers (e.g., vector, valarray, etc.) and into Haskell
> functions/methods/procedures/etc. While I might have missed such
> information when I performed a web search on the topic, I did not find any
> information to help. Any assistance in finding such material would be
> greatly appreciated.
>
> Sincerely,
> Frank D. Martinez
>
> --
> P.S.: I prefer to be reached on BitMessage at
> BM-2D8txNiU7b84d2tgqvJQdgBog6A69oDAx6
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20140813/cb105c76/attachment-0001.html>

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

Message: 3
Date: Wed, 13 Aug 2014 20:00:43 +0200
From: martin <martin.drautzb...@web.de>
To: beginners@haskell.org
Subject: [Haskell-beginners] State Monad  vs. fold
Message-ID: <53eba7cb.8000...@web.de>
Content-Type: text/plain; charset=ISO-8859-15

Hello all,

many times I see a problem and I say to myself: "there is some state". I then 
play around with the state monad and often
I don't get anywhere. Then at some point I realizes, that all I need is a 
simple fold. I don't think I ever used the
state monad outside of toy examples.

Can someone give me some insights when the State Monad is beneficial and where 
a fold is the better choice.


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

Message: 4
Date: Wed, 13 Aug 2014 13:30:36 -0500
From: "John Wiegley" <jo...@newartisans.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] State Monad  vs. fold
Message-ID: <m261hwjl83....@newartisans.com>
Content-Type: text/plain

>>>>> martin  <martin.drautzb...@web.de> writes:

> Can someone give me some insights when the State Monad is beneficial and
> where a fold is the better choice.

Looking at the type of a fold:

    foldr :: (a -> b -> b) -> b -> [a] -> b

If we juggle the arguments we get:

    foldr :: (a -> b -> b) -> [a] -> b -> b

And if we imagine State b () actions, we can directly rewrite this as:

    foldrS :: (a -> State b ()) -> [a] -> State b ()

Which generalizes to:

    foldrS :: MonadState b m => (a -> m ()) -> [a] -> m ()

Which is roughly the same thing as using mapM_ over our State monad:

    mapM_ :: Monad m => (a -> m b) -> [a] -> m ()

In other words, these two forms in our example say the same thing:

    foldr f b xs
    execState (mapM_ f' xs) b

With the only difference being the types of f and f':

    f  : a -> b -> b
    f' : a -> State b ()

The other question you asked is when to choose one over the other.  Since they
are equivalent, it's really up to you.  I tend to prefer using a fold over
State, to keep things on the level of functions and values, rather than
pulling in monads and possibly monad transformers unnecessarily.

But it's a very good thing to hold these isomorphisms in your mind, since you
can then freely switch from one representation to another as need be.  This is
true of a lot of type equivalences throughout Haskell, where the more things
you can see as being essentially the same, the more freedom you have to find
the best abstraction for a particular context.

John


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

Message: 5
Date: Wed, 13 Aug 2014 20:39:00 +0200
From: Vlatko Basic <vlatko.ba...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Too much mapM, fmap and concat
Message-ID: <53ebb0c4.1060...@gmail.com>
Content-Type: text/plain; charset=windows-1252; format=flowed

Hi Martin,

While fmap you might consider noise, mapM you can't. If you have a list, you 
have to map(M) over it. What you can do is use map(M) once, and combine 
functions that you're mapping over. That way there is only one pass over the 
list.

There is an operator (<$>) that is a synonym for fmap, so you can use that for 
noise reduction.

If you wanted to shorten the code, here is my try.


main = do
   fs <- concat . fst <$> globDir [compile filePattern] fileDirectory
   result <- mapM (fmap (concat . processFile) . nameAndContent) fs
   mapM_ putStrLn result
--  This one combines the two above
--  mapM_ (join . fmap (print . concat . processFile) . nameAndContent) fs
   where
     nameAndContent :: String -> IO (FilePath, [String])
     nameAndContent fn = do
       content <- lines <$> readFile fn
       return $ (fn, content)


vlatko

-------- Original Message  --------
Subject: [Haskell-beginners] Too much mapM, fmap and concat
From: martin <martin.drautzb...@web.de>
To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level 
topics related to Haskell <beginners@haskell.org>
Date: 13.08.2014 18:21

> Hello all,
>
> I never did much IO in haskell, but now I have to process some files. I catch 
> myself adding a mapM here and an fmap
> there. While it is clear to me what these functions do, I wonder if there is 
> a way to avoid the noise. Also I could not
> find a simple way to pair the lines of a file with its filename. I ended up 
> writing a function "nameAndContent". Finally
> I am amazed by the many "concat"s I need.
>
> Maybe these things just lie in the nature of the problem ("process a number 
> of files"). Otherwise any style suggestions
> would be much appreciated.
>
> import System.FilePath.Glob
> import Data.List
>
> filePattern="*.hs"
> fileDirectory = "."
>
> processFile :: (FilePath, [String]) -> [String]
> processFile (path, flines) = ["done"]
>
> main = do
>      matchingFiles <- fmap (concat . fst) $ globDir [compile filePattern] 
> fileDirectory
>      flines <- mapM nameAndContent matchingFiles
>      result <- mapM (return . processFile) flines
>      mapM putStrLn $ concat  result
>              where
>                  nameAndContent :: FilePath -> IO (FilePath, [String])
>                  nameAndContent fn = do
>                      content <- fmap lines $ readFile fn
>                      return (fn, content)
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>


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

Message: 6
Date: Wed, 13 Aug 2014 13:16:08 -0600
From: Dimitri DeFigueiredo <defigueir...@ucdavis.edu>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] expressing constraints 101
Message-ID: <53ebb978.4030...@ucdavis.edu>
Content-Type: text/plain; charset="iso-8859-1"; Format="flowed"

Thanks guys. It seems like type families are the way to go, but I am 
surprised that there is no way to express this in standard Haskell.

On a follow up note, will GADTs bring this into the main language? I 
seem to remember a talk by Simon PJ on how to build data structures 
whose representation depend on the types of their elements by using 
GADTs. Thinking about it now, it seems that's what I want here. If the 
elements are Ord-ered I can implement Set with a Tree, on the other 
hand, if they are only Eq and Hashable, I can use a hash table to 
implement Set.

Dimitri


Em 13/08/14 01:23, akash g escreveu:
> Hi Dimitri,
>
> Did a bit of research  and found type families to be a good fit for 
> this 
> (http://www.haskell.org/ghc/docs/latest/html/users_guide/type-families.html). 
> Type families lets us define the contraints (and a lot of other 
> things) when creating an instance.  I still do not know if this is the 
> ideal solution, but it is still a lot better than the previous 
> solution that I posted.
>
> {-# LANGUAGE ConstraintKinds #-}
> {-# LANGUAGE TypeFamilies #-}
> import GHC.Exts
>
> class Set s where
>   type C s a :: Constraint -- Here, the explicit type that we would 
> have given is turned into a type synonym of the kind Constraint, from 
> GHC.Exts.
>   empty         :: s a
>   insert        :: (C s a) =>  a -> s a -> s a
>   member        :: (C s a) => a -> s a -> Bool
>
>
> data Tree a = Empty | MkTree (Tree a) a (Tree a)
>
> treeEmpty :: Tree a
> treeEmpty = Empty
>
> treeInsert :: Ord a => a -> Tree a -> Tree a
> treeInsert = undefined
>
> treeMember :: Ord a => a -> Tree a -> Bool
> treeMember = undefined
>
> instance Set Tree where
>   type C Tree a = Ord a -- Here, we are setting the type constraint to 
> Ord a, where a is again a type variable.
>   empty  = treeEmpty
>   member = treeMember
>   insert = treeInsert
>
>
> - Akash G
>
>
>
>
>
> On Wed, Aug 13, 2014 at 11:41 AM, Dimitri DeFigueiredo 
> <defigueir...@ucdavis.edu <mailto:defigueir...@ucdavis.edu>> wrote:
>
>     Hi G Akash,
>
>     Is that the only solution? I thought about that. The problem with
>     it is that it changes the Set type class. I want the Set type
>     class to be able to contain elements of any type, not just members
>     of Ord.
>
>     I think the type class represents a "Set" interface that is
>     general. It is the implementation using trees that is only
>     available for Ordered types. And there may be other
>     implementations that don't need this constraint. So, if possible,
>     I don't want to change the Set type class. Isn't there another way
>     to fix it?
>
>
>     Thanks,
>
>
>     Dimitri
>
>
>     Em 12/08/14 23:18, akash g escreveu:
>>     Hi Dimitri,
>>
>>     You can express the constraints as below
>>
>>     class Set s where
>>       empty  :: s a               -- returns an empty set of type Set
>>     of a
>>       insert :: (Ord a) => a -> s a -> s a   -- returns set with new
>>     element inserted
>>       member :: (Ord a) => a -> s a -> Bool  -- True if element is a
>>     member of the Set
>>
>>     This is because when you define tree as an instance of the
>>     typeclass 'Set', you don't match the constraints on the functions
>>     that the functions that it wants you to implement  That is, when
>>     you do:
>>
>>
>>     treeInsert :: Ord a => a -> Tree a -> Tree a
>>     treeInsert = undefined
>>
>>     instance Set Tree where
>>       empty  = treeEmpty
>>       insert = treeInsert
>>       member = treeMember
>>
>>     The type signature doesn't match when you do insert=treeInsert or
>>     member=treeMember, since you have
>>
>>     class Set s where
>>        insert :: a -> s a -> s a
>>
>>     Hope this helps
>>
>>     - G Akash
>>
>>
>>
>>     On Wed, Aug 13, 2014 at 8:44 AM, Dimitri DeFigueiredo
>>     <defigueir...@ucdavis.edu <mailto:defigueir...@ucdavis.edu>> wrote:
>>
>>         Hi All,
>>
>>         I am working through an exercise in Chris Okasaki's book
>>         (#2.2). In the book, he is trying to implement a minimal
>>         interface for a Set. I wrote that simple interface in Haskell as:
>>
>>         class Set s where
>>             empty  :: s a                -- returns an empty set of
>>         type Set of a
>>             insert :: a -> s a -> s a   -- returns set with new
>>         element inserted
>>             member :: a -> s a -> Bool  -- True if element is a
>>         member of the Set
>>
>>         To implement that interface with the appropriately O(log n)
>>         insert and member functions he suggests the use of a Binary
>>         Search Tree, which I translated to Haskell as:
>>
>>         data Tree a = Empty | MkTree (Tree a) a (Tree a)
>>
>>         But for the tree to work, we also need the "a"s to be totally
>>         ordered. I.e. (Ord a) is a constraint. So, it makes sense to
>>         write:
>>
>>         treeEmpty :: Tree a
>>         treeEmpty = Empty
>>
>>         treeInsert :: Ord a => a -> Tree a -> Tree a
>>         treeInsert = undefined
>>
>>         treeMember :: Ord a => a -> Tree a -> Bool
>>         treeMember = undefined
>>
>>         Now, I would like to bind this implementation using Trees of
>>         an ordered type "a" to the set type class. So, I would like
>>         to write something like:
>>
>>         instance Set Tree where
>>             empty  = treeEmpty
>>             insert = treeInsert
>>             member = treeMember
>>
>>         But that doesn't work. Using GHC 7.6.3, I get a:
>>
>>             No instance for (Ord a) arising from a use of `treeInsert'
>>             Possible fix:
>>               add (Ord a) to the context of
>>                 the type signature for insert :: a -> Tree a -> Tree a
>>             In the expression: treeInsert a
>>             In an equation for `insert': insert a = treeInsert a
>>             In the instance declaration for `Set Tree'
>>
>>         Which makes sense, but I'm not sure how to express this
>>         constraint.
>>         So, what is the proper way to do this?
>>         Where have I gone wrong?
>>
>>
>>         Thanks!
>>
>>         Dimitri
>>
>>
>>
>>
>>
>>
>>         _______________________________________________
>>         Beginners mailing list
>>         Beginners@haskell.org <mailto:Beginners@haskell.org>
>>         http://www.haskell.org/mailman/listinfo/beginners
>>
>>
>>
>>
>>     _______________________________________________
>>     Beginners mailing list
>>     Beginners@haskell.org  <mailto:Beginners@haskell.org>
>>     http://www.haskell.org/mailman/listinfo/beginners
>
>
>     _______________________________________________
>     Beginners mailing list
>     Beginners@haskell.org <mailto:Beginners@haskell.org>
>     http://www.haskell.org/mailman/listinfo/beginners
>
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners

-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20140813/4adb3324/attachment.html>

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

Subject: Digest Footer

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


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

End of Beginners Digest, Vol 74, Issue 8
****************************************

Reply via email to