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.  Builds with cabal, but not with GHC (Amy de Buitl?ir)
   2. Re:  Builds with cabal, but not with GHC (Amy de Buitl?ir)
   3. Re:  Builds with cabal, but not with GHC (aditya siram)
   4. Re:  Builds with cabal, but not with GHC (Amy de Buitl?ir)
   5. Re:  Builds with cabal, but not with GHC (Brent Yorgey)
   6. Re:  Builds with cabal, but not with GHC (Daniel Fischer)
   7. Re:  Builds with cabal, but not with GHC (Amy de Buitl?ir)
   8. Re:  clarity and complexity of Haskell code? (Chadda? Fouch?)


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

Message: 1
Date: Wed, 28 Sep 2011 15:03:33 +0000 (UTC)
From: Amy de Buitl?ir <a...@nualeargais.ie>
Subject: [Haskell-beginners] Builds with cabal, but not with GHC
To: beginners@haskell.org
Message-ID: <loom.20110928t152219-...@post.gmane.org>
Content-Type: text/plain; charset=utf-8

I'm getting some weird errors when I try to compile this with GHC, or load it
in GHCi, but it compiles (and runs) just fine using cabal. Here's the file...

**********
FILE Test.hs:
**********
module Main where

import Control.Monad.Error ( runErrorT, ErrorT, join, liftIO )
import Data.ConfigFile ( get, CPError, emptyCP, readfile )

data Configuration = Configuration
  {
    popDir :: FilePath,
    username :: String,
    sleepTime :: Int
  } deriving Show

parseConfig :: ErrorT CPError IO Configuration
parseConfig = do
  cp <- join $ liftIO $ readfile emptyCP "/etc/creatur-daemon.conf"
  u <- Data.ConfigFile.get cp "DEFAULT" "user"
  pd <- Data.ConfigFile.get cp "DEFAULT" "dir"
  st <- Data.ConfigFile.get cp "DEFAULT" "sleeptime"
  return $ Configuration { popDir = pd, username = u, sleepTime = st }

main :: IO ()
main = do
  rv <- runErrorT parseConfig
  case rv of
       Left (_, msg) -> putStrLn msg
       Right config -> print config
**********

When I compile it with ghc, I get the following:

$ ghc -hide-package monads-fd Test.hs
[1 of 1] Compiling Main             ( Test.hs, Test.o )

Test.hs:20:9:
    No instance for (mtl-1.1.1.1:Control.Monad.Error.Class.MonadError
                       CPError (ErrorT CPError IO))
      arising from a use of `get'
    Possible fix:
      add an instance declaration for
      (mtl-1.1.1.1:Control.Monad.Error.Class.MonadError
         CPError (ErrorT CPError IO))
    In a stmt of a 'do' expression: st <- get cp "DEFAULT" "sleeptime"
    In the expression:
      do { cp <- join
               $   liftIO $ readfile emptyCP "/etc/creatur-daemon.conf";
           u <- get cp "DEFAULT" "user";
           pd <- get cp "DEFAULT" "dir";
           st <- get cp "DEFAULT" "sleeptime";
           .... }
    In an equation for `parseConfig':
        parseConfig
          = do { cp <- join
                     $   liftIO $ readfile emptyCP "/etc/creatur-daemon.conf";
                 u <- get cp "DEFAULT" "user";
                 pd <- get cp "DEFAULT" "dir";
                 .... }

Test.hs:21:3:
    No instance for (Error (CPErrorData, String))
      arising from a use of `return'
    Possible fix:
      add an instance declaration for (Error (CPErrorData, String))
    In the expression: return
    In the expression:
        return $ Configuration {popDir = pd, username = u, sleepTime = st}
    In the expression:
      do { cp <- join
               $   liftIO $ readfile emptyCP "/etc/creatur-daemon.conf";
           u <- get cp "DEFAULT" "user";
           pd <- get cp "DEFAULT" "dir";
           st <- get cp "DEFAULT" "sleeptime";
           .... }

I tried adding the instance declarations, but I don't think I did it right
because I then had to add a bunch of imports, and the problems just snowballed.

With this cabal file, I can do "cabal install", and the program compiles and
runs just fine.

**********
FILE: Creatur.cabal
**********

Name:               Creatur
Version:             2.0
Description:       Cr?at?r
License:             OtherLicense
License-file:       LICENSE
Author:              Amy de Buitl?ir
Maintainer:        a...@nualeargais.ie
Build-Type:          Simple
Cabal-Version:    >=1.2

Executable amy-test
  Main-Is:         Test.hs
  GHC-Options:     -Wall -Werror
  Build-Depends:     base >= 4 && < 5, mtl ==1.1.*, ConfigFile ==1.0.*
**********

Can anyone tell me how to modify the code so it will compile? Thank you in 
advance.




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

Message: 2
Date: Wed, 28 Sep 2011 15:14:19 +0000 (UTC)
From: Amy de Buitl?ir <a...@nualeargais.ie>
Subject: Re: [Haskell-beginners] Builds with cabal, but not with GHC
To: beginners@haskell.org
Message-ID: <loom.20110928t171029-...@post.gmane.org>
Content-Type: text/plain; charset=utf-8

Amy de Buitl?ir <amy <at> nualeargais.ie> writes:
> Can anyone tell me how to modify the code so it will compile? Thank you in 
> advance.

Sorry, I meant to say "Can anyone tell me how to modify the code so it will
build in ghc[i]? It already builds with cabal.




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

Message: 3
Date: Wed, 28 Sep 2011 10:24:05 -0500
From: aditya siram <aditya.si...@gmail.com>
Subject: Re: [Haskell-beginners] Builds with cabal, but not with GHC
To: Amy de Buitl?ir <a...@nualeargais.ie>
Cc: beginners@haskell.org
Message-ID:
        <CAJrReygkZVtmpQi=xKfHPY0SiWJSzdwp0c_Hx_7=rioy8q6...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I couldn't get the configfile package to install because of issues
installing MissingH, but looking at the error messages the first thing I'd
do is to change the import list to:
import Control.Monad.Error
import Data.ConfigFile

-deech


On Wed, Sep 28, 2011 at 10:14 AM, Amy de Buitl?ir <a...@nualeargais.ie>wrote:

> Amy de Buitl?ir <amy <at> nualeargais.ie> writes:
> > Can anyone tell me how to modify the code so it will compile? Thank you
> in
> > advance.
>
> Sorry, I meant to say "Can anyone tell me how to modify the code so it will
> build in ghc[i]? It already builds with cabal.
>
>
> _______________________________________________
> 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/20110928/e57e1937/attachment-0001.htm>

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

Message: 4
Date: Wed, 28 Sep 2011 15:29:30 +0000 (UTC)
From: Amy de Buitl?ir <a...@nualeargais.ie>
Subject: Re: [Haskell-beginners] Builds with cabal, but not with GHC
To: beginners@haskell.org
Message-ID: <loom.20110928t172723-...@post.gmane.org>
Content-Type: text/plain; charset=us-ascii

aditya siram <aditya.siram <at> gmail.com> writes:

> I couldn't get the configfile package to install because of issues installing
> MissingH, but looking at the error messages the first thing I'd do is to 
> change
> the  import list to:
> import Control.Monad.Error
> import Data.ConfigFile

Sorry, I forgot to mention that I had already tried doing that, but it didn't
help.




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

Message: 5
Date: Wed, 28 Sep 2011 11:37:14 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Builds with cabal, but not with GHC
To: beginners@haskell.org
Message-ID: <20110928153714.ga11...@seas.upenn.edu>
Content-Type: text/plain; charset=iso-8859-1

On Wed, Sep 28, 2011 at 03:03:33PM +0000, Amy de Buitl?ir wrote:
> 
> Test.hs:20:9:
>     No instance for (mtl-1.1.1.1:Control.Monad.Error.Class.MonadError
>                        CPError (ErrorT CPError IO))

I don't know a solution, but just want to point out that this error
message smacks of inconsistent package versions being used.  Something
else used mtl-1.1.1.1 and the current module is being compiled with a
different version of mtl, or something like that.  Hopefully this can
provide a fruitful direction of investigation...

-Brent



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

Message: 6
Date: Wed, 28 Sep 2011 17:37:54 +0200
From: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Subject: Re: [Haskell-beginners] Builds with cabal, but not with GHC
To: beginners@haskell.org
Cc: Amy de Buitl?ir <a...@nualeargais.ie>
Message-ID: <201109281737.55078.daniel.is.fisc...@googlemail.com>
Content-Type: Text/Plain;  charset="utf-8"

On Wednesday 28 September 2011, 17:03:33, Amy de Buitl?ir wrote:
> I'm getting some weird errors when I try to compile this with GHC, or
> load it in GHCi, but it compiles (and runs) just fine using cabal.
> Here's the file...
> 
<snip>
> 
> When I compile it with ghc, I get the following:
> 
> $ ghc -hide-package monads-fd Test.hs
> [1 of 1] Compiling Main             ( Test.hs, Test.o )
> 
> Test.hs:20:9:
>     No instance for (mtl-1.1.1.1:Control.Monad.Error.Class.MonadError
>                        CPError (ErrorT CPError IO))

That's a hint.
The error message mentions the specific version of the package in which the 
class is defined.
That usually means you are/the compiler is trying to build using 
incompatible packages. In this case, it looks as though the used ConfigFile 
was built against something other than mtl-1.1.1.1, maybe mtl-2.*

Have you different versions of ConfigFile installed?


> 
> I tried adding the instance declarations, but I don't think I did it
> right because I then had to add a bunch of imports, and the problems
> just snowballed.

If the used packages are incompatible, the given 'probable fix' will not 
work, the problem lies deeper. The missing instance is just the place where 
ghc notices that it won't work, without figuring out the exact cause.

> 
> With this cabal file, I can do "cabal install", and the program compiles
> and runs just fine.
> 
> **********
> FILE: Creatur.cabal
> **********
> 
> Name:               Creatur
> Version:             2.0
> Description:       Cr?at?r
> License:             OtherLicense
> License-file:       LICENSE
> Author:              Amy de Buitl?ir
> Maintainer:        a...@nualeargais.ie
> Build-Type:          Simple
> Cabal-Version:    >=1.2
> 
> Executable amy-test
>   Main-Is:         Test.hs
>   GHC-Options:     -Wall -Werror
>   Build-Depends:     base >= 4 && < 5, mtl ==1.1.*, ConfigFile ==1.0.*
> **********

Yes, Cabal sees the dependencies and chooses a compatible set of versions 
(if possible, otherwise it fill fail and tell you why).
GHC only sees which packages are needed when following the imports during 
compilation, so it doesn't create a consistent install plan but just 
chooses the latest available version of each package and hopes for the 
best.

> 
> Can anyone tell me how to modify the code so it will compile? Thank you
> in advance.

You don't need to change the source, just the command line. You have to 
tell GHC explicitly which packages to use.

$ cabal install --dry-run -v3

in the package directory will give you a lot of output, you're interested 
in the "selecting xyz-0.1.2" bits.

Then

$ ghc -hide-all-packages -package base -package mtl-1.1.1.1 -package 
ConfigFile-1.0.? Test.hs

should work.




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

Message: 7
Date: Wed, 28 Sep 2011 15:50:08 +0000 (UTC)
From: Amy de Buitl?ir <a...@nualeargais.ie>
Subject: Re: [Haskell-beginners] Builds with cabal, but not with GHC
To: beginners@haskell.org
Message-ID: <loom.20110928t174438-...@post.gmane.org>
Content-Type: text/plain; charset=us-ascii

Daniel Fischer <daniel.is.fischer <at> googlemail.com> writes:
> (a brilliant explanation)

Wow! Now the problem (and solution) is clear. And that cabal install --dry-run
-v3 will come in very handy for diagnosing similar problems. Thank you so much.




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

Message: 8
Date: Wed, 28 Sep 2011 22:20:26 +0200
From: Chadda? Fouch? <chaddai.fou...@gmail.com>
Subject: Re: [Haskell-beginners] clarity and complexity of Haskell
        code?
To: Ozgur Akgun <ozgurak...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <CANfjZRa=dgeakdhhac7q5r+_aodkvf+rwu2htzrzlpawg5x...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Sun, Sep 25, 2011 at 10:05 PM, Ozgur Akgun <ozgurak...@gmail.com> wrote:
> Hi.
>
> On 25 September 2011 18:10, Brent Yorgey <byor...@seas.upenn.edu> wrote:
>>
>> You must at least agree that it is short.
>
> Not trying to start language wars here, but it is not terribly short for
> what it does. The following code does the same thing in C#, and isn't far
> longer. And it has more or less a one-to-one correspondence to the given
> Haskell code; open a file for reading, open a file for writing, read some
> number of bytes, apply the transformation, write it to the output file.
> Flushing the input/output buffers and closing the files are handled by the
> using construct, similar to withFile in the Haskell example.
> int chunksize = 4096;
> using (var r = new BinaryReader(File.OpenRead("infile")))
> ? ? using (var w = new BinaryWriter(File.OpenWrite("outfile")))
> ? ? ? ? for (var buffer = r.ReadBytes(chunksize); buffer.Length > 0; buffer
> = r.ReadBytes(chunksize))
> ? ? ? ? ? ? w.Write(Array.ConvertAll(buffer, p => (byte) ~p));

Note that this code is pretty close to FP already (except the "for"
loop which is where the iteratees/enumerator that present the main
difficulty in Haskell trying to do the FP equivalent intervene) : the
"using" is pretty declarative, you use a closure and a higher order
function...

-- 
Jeda?



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

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


End of Beginners Digest, Vol 39, Issue 36
*****************************************

Reply via email to