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.  Map instances in the list-tries package (Matthew Moppett)
   2. Re:  Map instances in the list-tries package (Stephen Tetley)
   3. Re:  Map instances in the list-tries package (Matthew Moppett)
   4. Re:  FFI export lazy list of string (Alexander.Vladislav.Popov )
   5.  llvm haskell bindings (Philippe Sismondi)
   6. Re:  llvm haskell bindings (Antoine Latter)
   7.  error logging (Dennis Raddle)
   8. Re:  error logging (Stephen Tetley)


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

Message: 1
Date: Mon, 19 Dec 2011 23:02:42 +1100
From: Matthew Moppett <matthewmopp...@gmail.com>
Subject: [Haskell-beginners] Map instances in the list-tries package
To: beginners@haskell.org
Message-ID:
        <CAMLEjZDz+yfk_n9ExNYxQ4urAtwe6nnJPJVENA=adw1nozc...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I want to use the list-tries package for a little hobby project, but my
naive idea about how it should work is obviously wrong:

module TryPat where
import Data.ListTrie.Patricia.Map

a = singleton "harry" 99

yields the error:

    No instance for (Data.ListTrie.Base.Map.Map map0 Char)
      arising from a use of `singleton'
    Possible fix:
      add an instance declaration for
      (Data.ListTrie.Base.Map.Map map0 Char)
    In the expression: singleton "harry" 99
    In an equation for `a': a = singleton "harry" 99

Now, there is some stuff about this in the docs:

  The data types are parametrized over the map type they use internally to
  store the child nodes: this allows extending them to support different
kinds
  of key types or increasing efficiency. Child maps are required to be
  instances of the Map class in
Data.ListTrie.Base.Map<http://hackage.haskell.org/packages/archive/list-tries/0.4.1/doc/html/Data-ListTrie-Patricia-Map.html>.
Some operations
  additionally require an OrdMap instance.

But frankly, I don't understand it, especially the type signatures. Any
hints on how I might go about making an instance for Map map0 Char?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111219/626d8977/attachment-0001.htm>

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

Message: 2
Date: Mon, 19 Dec 2011 14:07:28 +0000
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] Map instances in the list-tries
        package
To: Matthew Moppett <matthewmopp...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <CAB2TPRC0t0QMSXWt5=cfqng9rs3d+pvzz_+94sk5+0melc7...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi Matthew

You'll have to give `a` a concrete type, as `singleton` is overloaded,
GHC cannot infer a type.

The TrieMap type is quite complicated as it allows different
representations of (finite) Maps within it. There are three different
internal maps you can use (the three pre-defined instances of the Map
class - Data.Map, WrappedIntMap and AList) - I'd go for Data.Map as it
will be faster than AList and I think you are using Char for key so
you can't use an IntMap.

I don't have the package `list-tries` installed but I'd guess at one
of these two for the concrete type signature.

Assuming you have imported Data.Map as

import qualified Data.Map as Map

(Probably this...)
a :: TrieMap Map.Map [Char] Int


(Possibly this...)
a :: TrieMap (Map.Map Char Int) [Char] Int



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

Message: 3
Date: Tue, 20 Dec 2011 02:52:10 +1100
From: Matthew Moppett <matthewmopp...@gmail.com>
Subject: Re: [Haskell-beginners] Map instances in the list-tries
        package
To: Stephen Tetley <stephen.tet...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <CAMLEjZBOvf1EbvUn7TWA54D64-fMw_zfnx_=f7ygsqqvzoe...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Thanks a lot, Stephen - was just about giving up on this.

The correct type signature turned out to be:

import Data.ListTrie.Patricia.Map as P
import qualified Data.Map as Map

a :: P.TrieMap Map.Map Char Int
a = P.singleton "harry" 99



On Tue, Dec 20, 2011 at 1:07 AM, Stephen Tetley <stephen.tet...@gmail.com>wrote:

> Hi Matthew
>
> You'll have to give `a` a concrete type, as `singleton` is overloaded,
> GHC cannot infer a type.
>
> The TrieMap type is quite complicated as it allows different
> representations of (finite) Maps within it. There are three different
> internal maps you can use (the three pre-defined instances of the Map
> class - Data.Map, WrappedIntMap and AList) - I'd go for Data.Map as it
> will be faster than AList and I think you are using Char for key so
> you can't use an IntMap.
>
> I don't have the package `list-tries` installed but I'd guess at one
> of these two for the concrete type signature.
>
> Assuming you have imported Data.Map as
>
> import qualified Data.Map as Map
>
> (Probably this...)
> a :: TrieMap Map.Map [Char] Int
>
>
> (Possibly this...)
> a :: TrieMap (Map.Map Char Int) [Char] Int
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111220/6773de06/attachment-0001.htm>

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

Message: 4
Date: Mon, 19 Dec 2011 22:41:47 +0600
From: "Alexander.Vladislav.Popov "
        <alexander.vladislav.po...@gmail.com>
Subject: Re: [Haskell-beginners] FFI export lazy list of string
To: "Edward Z. Yang" <ezy...@mit.edu>
Cc: beginners <beginners@haskell.org>
Message-ID:
        <calpbq9ahrbd6yuhhl-itv6tnys6ys9uujjlfqwc8z3drfyh...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi, Edward.

Thank you very much for your help. Very concisely.Russian say: brevity is
the sister of talent. I made my own naive
solution<http://rsdn.ru/forum/decl/4543044.1.aspx> which
based on VoidEx's advise <http://rsdn.ru/forum/decl/4541766.1.aspx>. In
Russian, but I think, you'll see the idea. It has some noise such as
CLazyList what is no more than code atavism from previous versions.

Happy hacking, too!
Alexander.

2011/12/16 Edward Z. Yang <ezy...@mit.edu>

> I did a writeup for an even simpler example, which hopefully will give you
> the
> right idea how to do it in your case:
>
>    http://blog.ezyang.com/2011/12/accessing-lazy-structures-from/
>
> Cheers,
> Edward
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111219/3ebdd308/attachment-0001.htm>

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

Message: 5
Date: Mon, 19 Dec 2011 13:10:23 -0500
From: Philippe Sismondi <psismo...@arqux.com>
Subject: [Haskell-beginners] llvm haskell bindings
To: Beginners Haskell <Beginners@haskell.org>
Message-ID: <26be8bff-2ab5-4f55-a8e2-71553fc93...@arqux.com>
Content-Type: text/plain; charset=us-ascii

I am running OS X 10.6.8 with Xcode 4. I have the Haskell Platform installed, 
ghc v. 7.0.3.

I cannot get the llvm haskell bindings to install correctly using cabal. I get 
this at the tail end of messages from cabal:

checking llvm-c/Core.h usability... yes
checking llvm-c/Core.h presence... yes
checking for llvm-c/Core.h... yes
checking llvm/Support/DynamicLibrary.h usability... yes
checking llvm/Support/DynamicLibrary.h presence... yes
checking for llvm/Support/DynamicLibrary.h... yes
checking for LLVMModuleCreateWithName in -lLLVMCore... no
checking for LLVMModuleCreateWithName in -lLLVMCore... no
configure: error: could not find LLVM C bindings
cabal: Error: some packages failed to install:
llvm-0.10.0.1 failed during the configure step. The exception was:
ExitFailure 1


Has anyone had any luck getting this set up? Googling leads me to some rather 
terse comments that the Apple llvm installation does not include the required 
llvm libraries. I hate to install a separate set of llvm stuff with macports, 
or the llvm repository, because I fear that I might run into all kinds of 
puzzling conflicts with the Apple stuff.

Ideas?

- P -


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

Message: 6
Date: Mon, 19 Dec 2011 13:21:03 -0500
From: Antoine Latter <aslat...@gmail.com>
Subject: Re: [Haskell-beginners] llvm haskell bindings
To: Philippe Sismondi <psismo...@arqux.com>
Cc: Beginners Haskell <Beginners@haskell.org>
Message-ID:
        <CAKjSnQFNpyC99YrSjQunY=poo+pfgjgq7kmnuufjby7h1oh...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Mon, Dec 19, 2011 at 1:10 PM, Philippe Sismondi <psismo...@arqux.com> wrote:
> I am running OS X 10.6.8 with Xcode 4. I have the Haskell Platform installed, 
> ghc v. 7.0.3.
>
> I cannot get the llvm haskell bindings to install correctly using cabal. I 
> get this at the tail end of messages from cabal:
>
> checking llvm-c/Core.h usability... yes
> checking llvm-c/Core.h presence... yes
> checking for llvm-c/Core.h... yes
> checking llvm/Support/DynamicLibrary.h usability... yes
> checking llvm/Support/DynamicLibrary.h presence... yes
> checking for llvm/Support/DynamicLibrary.h... yes
> checking for LLVMModuleCreateWithName in -lLLVMCore... no
> checking for LLVMModuleCreateWithName in -lLLVMCore... no

Here, configure has found LLVM C library, but the found library does
not have the functionality required.

> configure: error: could not find LLVM C bindings

So here configure reports that it cannot find LLVM C library.

> cabal: Error: some packages failed to install:
> llvm-0.10.0.1 failed during the configure step. The exception was:
> ExitFailure 1
>
>
> Has anyone had any luck getting this set up? Googling leads me to some rather 
> terse comments that the Apple llvm installation does not include the required 
> llvm libraries. I hate to install a separate set of llvm stuff with macports, 
> or the llvm repository, because I fear that I might run into all kinds of 
> puzzling conflicts with the Apple stuff.
>

It looks like your guess is correct - the LLVM C library you have
installed isn't what the Haskell bindings want.

> Ideas?
>

This might be where someone else jumps in - I've had luck with
MacPorts + Haskell in the past, but it can be a struggle. I've never
tried this particular case.

In particular the iconv situation is nightmarish (Apple iconv and
MacPorts iconv are not ABI compatible), but that's really a special
case of the more general problem of building things against MacPorts.

Antoine



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

Message: 7
Date: Mon, 19 Dec 2011 16:32:42 -0800
From: Dennis Raddle <dennis.rad...@gmail.com>
Subject: [Haskell-beginners] error logging
To: Haskell Beginners <beginners@haskell.org>
Message-ID:
        <CAKxLvooCwrdhbT+EL6obL5PmaGSzjqSg4qXr4=fajohe7be...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Okay, I want to write code in the Either monad in order to throw errors
with logging. I did this a while ago but can't find my code and I forget
what I did.

Note that I'm using ghc 6.12.3, which I installed via the haskell platform.

First question is: do I use Control.Monad.Error or Control.Monad.Either?

Second question is: I want to have each monadic function within the stack
of functions that is currently running catch the error and add some context
to the log.

For instance I need to have a function called, let's say,
"catchAndAnnotate" that functions like the following. I'm just making this
up-- how is it really done?

func1 :: SomeType -> Either String SomeType
func1 x = ("running in func1 with argument " ++ show x) `catchAndAnnotate`
  (do y <- somework x
        when (isBad y) (throwError "oops")
        return y)

somework :: SomeType -> Either String SomeType
somework x = ("running in somework with argument ++ show x)
`catchAndAnnotate` (whatever x)

whatever :: SomeType -> Either String SomeType
whatever = ...
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111219/94415485/attachment-0001.htm>

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

Message: 8
Date: Tue, 20 Dec 2011 07:55:36 +0000
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] error logging
To: Dennis Raddle <dennis.rad...@gmail.com>
Cc: Haskell Beginners <beginners@haskell.org>
Message-ID:
        <cab2tprbcxydrgfxlj9reojmhff+m64qzfkfcg8xrdqmjexb...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi Dennis

If you want logging you probably want a Writer monad. Either / error
monads only support single message on failure. For logging you have to
pass an accumulator throughout the computation so it can store
messages - this is what Writer does.

If you want logging and error you probably want a combined Error and
Writer monad.



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

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


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

Reply via email to