Re: [Haskell-cafe] Rigid type variable error

2009-06-27 Thread Jason Dagit
On Fri, Jun 26, 2009 at 8:48 PM, Darryn djr...@aapt.net.au wrote:

  From:
 Darryn djr...@aapt.net.au
To:
 beginn...@haskell.org
   Subject:
 Rigid type variables match error
  Date:
 Sat, 27 Jun 2009 10:18:13 +0930


 Hi, I wonder if anyone can explain what is going on here and what to do
 about it. I'm fairly new to Haskell, so apologies in advance if my
 question seems naive. I've cut my code down to a minimum that reproduces
 the problem. I receive an error in GHCI in the following code,
 complaining that it cannot match the rigid type variables for the
 instance definition for Ainst for the function a3. Can anyone advise
 about what to do about it?

 
 class A a where
a1 :: a
a2 :: a - a
a3 :: (B b) = b - a

 class B b where
b1 :: Int - b

 data (B b) = Ainst b = I | J (Ainst b) | K b

 instance (B b) = A (Ainst b) where
a1 = I
 --  a2 :: (B b, A a) = a - a
a2 = J
 --  a3 :: (B b, A a) = b - a
a3 = K -- Error!
 --  a3 = K `asTypeOf` a3   -- Error even with this!

 data Binst = Val Int

 instance B Binst where
b1 = Val
 

 Test5.hs:17:9:
Couldn't match expected type `b1' against inferred type `b'
  `b1' is a rigid type variable bound by
   the instance declaration at Test5.hs:12:12
  `b' is a rigid type variable bound by
  the type signature for `a3' at Test5.hs:5:13
  Expected type: b - Ainst b1
  Inferred type: b - Ainst b
In the expression: K `asTypeOf` a3
In the definition of `a3': a3 = K `asTypeOf` a3
 Failed, modules loaded: none.

 Thanks in advance for any help anyone can provide.


Let me rephrase your definitions slightly:
instance (B b1) = A (Ainst b1) where
   a1 = I
--  a2 :: (B b1, A a) = a - a
   a2 = J
--  a3 :: (B b1, A a) = b - a
   a3 = K -- Error!
--  a3 = K `asTypeOf` a3   -- Error even with this!

This is the way the type system sees your types.  Notice that in the type
signature of a3, it has no way to know that b1 is the same as b, and worse
yet, b is totally free and b1 is not (must be an instance of B), so it
thinks they cannot be unified.  Which is to say, in general they may range
over different types.

I would recommend removing the type class constraint from the definition of
Ainst.  I haven't tried it, but I think that will make life easier for you.

Jason
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Trivial pivoting for the DSP lu decomposition

2009-06-27 Thread Fernan Bolando
Hi all

I created the beginnings of a simple circuit simulator using haskell.
It can be downloaded
from.
http://plan9.bell-labs.com/sources/contrib/fernan/escomma.tar.bz2

It uses a modified version of the haskell DSP library matrix. I
extended it with a simple pivoting
Its not very haskelly, but it works with matrices that didn't work
with the unmodified version.

thanks for those that answered my list processing questions. I used
that code to create
a permutation vector for the pivoting.

I am now looking into non-linear matrix solver. does anybody have a
reference code for that?

fernan
-- 
http://www.fernski.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A Reader Monad Tutorial

2009-06-27 Thread Henry Laxen
Dear Group,

If any of you are struggling with understanding monads, I've tried to put
together a pretty through explanation of what is behind the Reader monad.  If
you're interested, have a look at:

http://www.maztravel.com/haskell/readerMonad.html

Enjoy.
Henry Laxen


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] F# mailing list?

2009-06-27 Thread GüŸnther Schmidt

Hi guys,

is there a mailing list for haskellers that defected to F#?

Not that I was I going to, just asking, absolutely hypothetically. Uhm.

Günther

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] F# mailing list?

2009-06-27 Thread Anton Tayanovskyy
Hi Günther, I would be interested in one too. I'm a Haskeller
currently working for an F# shop. There's hubFS but I would absolutely
prefer a mailing list. --A

On Sat, Jun 27, 2009 at 8:31 PM, GüŸnther Schmidtgue.schm...@web.de wrote:
 Hi guys,

 is there a mailing list for haskellers that defected to F#?

 Not that I was I going to, just asking, absolutely hypothetically. Uhm.

 Günther

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Kind Regards,

Anton Tayanovskyy
F# Developer

IntelliFactory, Budapest - Hungary
www.intellifactory.com http://www.intellifactory.com/

DISCLAIMER AND CONFIDENTIALITY CAUTION:
This message and any of its attachments (message) are intended
solely for the use of the addressees and contain information that is
legally privileged and confidential. Any unauthorized dissemination,
distribution or copying is strictly prohibited. If you received this
message in error you are obliged to delete it, destroy any printed
copies, and notify the sender.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: F# mailing list?

2009-06-27 Thread GüŸnther Schmidt

Hi Anton,

cool I'll keep you in the loop.

Would you mind talking about more about what you do in the F# Shop?

I must admit I only came to haskell itself only 2 years ago, created 2 
apps in it and have no clue for instance on how F# standing in the 
market is.



Günther


Anton Tayanovskyy schrieb:

Hi Günther, I would be interested in one too. I'm a Haskeller
currently working for an F# shop. There's hubFS but I would absolutely
prefer a mailing list. --A

On Sat, Jun 27, 2009 at 8:31 PM, GüŸnther Schmidtgue.schm...@web.de wrote:

Hi guys,

is there a mailing list for haskellers that defected to F#?

Not that I was I going to, just asking, absolutely hypothetically. Uhm.

Günther

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe








___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Could FFI support pass-by-value of structs?

2009-06-27 Thread Henning Thielemann
Maurí­cio schrieb:
 It's not usual, but it is allowed to have values of
 structs passed between functions directly instead of
 using pointers: (...)
 
 Would it be possible to allow that in Haskell FFI (...)
 
 There are a couple problems with this. First, the storage layout for a
 given C struct may be radically different depending on the back end,
 
 When you say struct layout, do you mean the offset of diferent
 fields? I don't think this would be a problem, as your sugestion
 of hsc2hs is one of many solutions to that. I'm not sugesting
 that peek and poke methods of Storage instances should be created
 automatically, I understand this would not worth the effort.
 
 However, isn't just knowing the size and alignment enough to
 write a generic struct handler that, by using the appropriate
 calling convention, is going to work with any struct? If not,
 I agree with you it's really not worth it (as we can use pointers
 as Felipe sugested.

I tried that in
  http://hackage.haskell.org/package/storable-record/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: Cal3D animation library

2009-06-27 Thread Gregory D. Weber
The Cal3D for Haskell project provides a partial binding to the C++ Cal3D 
animation library.  The project homepage is

http://haskell.org/haskellwiki/Cal3d_animation

There are three packages available on hackage:

* cal3d-0.1 is a Haskell binding to the Cal3D library itself.

* cal3d-opengl-0.1 adds a few functions for using Cal3D with OpenGL.

* cal3d-examples-0.1 provides a simple example based on the Cally Demo.

Cal3D is a C++ library for skeletal-based character animation. 
It is platform-independent and independent of any particular
graphics API.  In fact, it does not actually render the animation,
but provides hooks that the graphics API (such as OpenGL) can use
to do the actual drawing. (As far as I know, though, the only 
graphics API available for Haskell is OpenGL.)

For more information about the (C++) Cal3D library, please see

* Cal3D FAQ:

http://cal3d.sourceforge.net/docs/api/html/cal3dfaq.html

* Cal3D Homepage:

http://home.gna.org/cal3d/

-- 
   ___   ___  __ _  
  / _ \ / _ \| || | Gregory D. Weber, Associate Professor
 / /_\// / | | | /\ | | Indiana University East
/ /_\\/ /__| | |/  \| | http://mypage.iu.edu/~gdweber/
\/\_/\___/\__/  Tel. (765) 973-8420; FAX (765) 973-8550
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Network.CGI -- practical web programming example.

2009-06-27 Thread Edward Ing
I am somewhat new to haskell. It is amazing that I can actually write
a CGI program using Network.CGI without really being comfortable with
the Haskell type system. Especially when it involves monad
transformations.
So I decided that I better understand this. I looked at the Practical
Web Programming examples to try to understand what is going on. I came
up with a problem that might demonstrate my misunderstanding. I am
wondering if you can answer questions I have. Code 1 is the example
from PWP, Code 2 is my variation and it works so I am stumped by what
the liftM is required.

code 1
#!/usr/bin/runghc
import Network.CGI
import Text.XHtml

import qualified Data.ByteString.Lazy as BS

import Control.Monad (liftM)
import Data.Maybe (fromJust)

uploadDir = ../upload

fileForm = form ! [method post, enctype multipart/form-data]
             [afile file, submit  Upload]
saveFile n =
   do          cont - (liftM fromJust) $ getInputFPS file
        let f = uploadDir ++ / ++ basename n
        liftIO $ BS.writeFile f cont
        return $ paragraph  (Saved as  +++ anchor ! [href f]  f +++ .)

page t b = header  thetitle  t +++ body  b

basename = reverse . takeWhile (`notElem` /\\) . reverse

cgiMain =
   do mn - getInputFilename file
      h - maybe (return fileForm) saveFile mn
      output $ renderHtml $ page Upload example h

main = runCGI $ handleErrors cgiMain

Code 2 (modifier) 

import Network.CGI
import Text.XHtml

import qualified Data.ByteString.Lazy as BS

import Control.Monad (liftM)
import Data.Maybe (fromJust)

uploadDir = ../upload

fileForm = form ! [method post, enctype multipart/form-data]
             [afile file, submit  Upload]
saveFile n =
do   cont - getInputFPS file
       let f = uploadDir ++ / ++ basename n
      liftIO $ BS.writeFile f (fromJust cont)
      return $ paragraph  (Saved as  +++ anchor ! [href f]  f +++ .)

page t b = header  thetitle  t +++ body  b

basename = reverse . takeWhile (`notElem` /\\) . reverse

cgiMain =
   do mn - getInputFilename file
      h - maybe (return fileForm) saveFile mn
      output $ renderHtml $ page Upload example h

main = runCGI $ handleErrors cgiMain



Questions ===

1) Why did the author choose to insert liftM in function saveFile?
It doesn't seem necessary in my version.

2) My background mainly is Java but here is my understanding of Monad
Transforms. The CGIT m type carries around with it the CGI Request
context and response contexts. The transformations (lifts) is similar
to casting so that you can use the functions for specific
manifestations but it also encapsulates the data. Is this correct?


Edward
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Network.CGI -- practical web programming example.

2009-06-27 Thread Luke Palmer
Your code examples are:

On Sat, Jun 27, 2009 at 6:07 PM, Edward Ing edward@gmail.com wrote:

 saveFile n =
do  cont - (liftM fromJust) $ getInputFPS file
 let f = uploadDir ++ / ++ basename n
 liftIO $ BS.writeFile f cont
 return $ paragraph  (Saved as  +++ anchor ! [href f]  f +++
 .)


Vs.


 saveFile n =
 do   cont - getInputFPS file
let f = uploadDir ++ / ++ basename n
   liftIO $ BS.writeFile f (fromJust cont)
   return $ paragraph  (Saved as  +++ anchor ! [href f]  f +++
 .)


Consider the line x - y in a do expression.  If y has type M a for some
monad M, then x has type a.

So, let's say you have a value f :: Maybe Int, and you want to return the
Int's stringification if it exists.  We can write this in these two ways:

do x - f
   return (show x)

do x - liftM show f
   return x

liftM :: (a - b) - (M a - M b)   for any monad M.  That means if you want
to apply a function to a value which is currently wrapped in a monad
constructor, you need to lift it in.  liftM takes a function on ordinary
values to a function on wrapped values.  But *after* you bind, you don't
need to lift anymore.

Which of the two above styles to choose is a matter of style, and, in my
code at least, varies from situation to situation.

That said, you can write both of these snippets as fmap show f or show
$ f  (where ($) is from Control.Applicative), which is how it would be
done in practice.

Does that make sense?
Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Network.CGI -- practical web programming example.

2009-06-27 Thread Brandon S. Allbery KF8NH

On Jun 27, 2009, at 20:07 , Edward Ing wrote:

saveFile n =
   do  cont - (liftM fromJust) $ getInputFPS file
let f = uploadDir ++ / ++ basename n
liftIO $ BS.writeFile f cont
return $ paragraph  (Saved as  +++ anchor ! [href f]   
f +++ .)


saveFile n =
do   cont - getInputFPS file
   let f = uploadDir ++ / ++ basename n
  liftIO $ BS.writeFile f (fromJust cont)
  return $ paragraph  (Saved as  +++ anchor ! [href f]  f + 
++ .)


1) Why did the author choose to insert liftM in function saveFile?



It's because of where fromJust is being called.  In yours, it's being  
used at a place that expects a normal value, so you can just go ahead  
and use it.


The original is applying the fromJust inside of a monadic computation,  
as indicated by the (-), so it needs to be lifted.  Some Haskell  
programmers use fmap (because most Monads are also Functors), others  
use liftM.  Both have the same effect:  given a monadic computation m  
a, liftM f turns f into a function that operates on the enclosed  
a instead of the entire m a.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] bizarre syntax error

2009-06-27 Thread Geoffrey Irving
I ran into a unfortunate syntax error just now.  I figured I'd share
it because it's the weirdest message I've ever gotten out of ghc.  The
broken code is

case t of
  TyApply tv types - do
(tvl, cases) - lookupDatatype prog tv
let tenv = Map.fromList (zip tvl types)  -- GHC POINTS HERE
caseType (c,vl,e')
  | Just tl - List.lookup c cases =
  if length vl == a then
expr prog global (foldl (\e (v,t) - Map.insert v
t e) env (zip vl (map (subst tenv) tl))) e'
  else
typeError (arity mismatch in pattern: ++show
(pretty c)++ expected ++show a++ argument++(if a == 1 then  else
s)
  ++ but got [++concat (intersperse ,  (map
(show . pretty) vl))++])
  where a = length tl -- THIS IS THE PROBLEM
  | otherwise = typeError (datatype ++show (pretty
tv)++ has no constructor ++show (pretty c))
defaultType Nothing = return []
defaultType (Just (v,e')) = expr prog global (Map.insert v
t env) e' =. \t - [t]
join t1 t2 | Just t - unifyS t1 t2 = return t
   | otherwise = typeError (failed to unify types
++show (pretty t1)++ and ++show (pretty t2)++ from different case
branches)
caseResults - mapM caseType pl
defaultResults - defaultType def
foldM1 join (caseResults ++ defaultResults)
  _ - typeError (expected datatype, got ++show (pretty t))

ghc complains that

The last statement in a 'do' construct must be an expression

and points to the line declaring tenv.  The actual problem is that
you can't put a where block in between two pattern guards. :)

Geoffrey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] bizarre syntax error

2009-06-27 Thread Brandon S. Allbery KF8NH

On Jun 27, 2009, at 20:37 , Geoffrey Irving wrote:

   The last statement in a 'do' construct must be an expression



Right, the where terminates the entire expression, you can't use it  
in the middle like that.  I'm pretty sure that's mandatory per the  
standard, and nobody really wants to open the can of worms involved  
with allowing its nested use as an extension.  (Layout is hard enough  
to parse already; IIRC, strictly speaking, the behavior specified in  
the standard is impossible to implement, and even almost right is  
extremely difficult.)  Use a subsidiary let instead:



   caseType (c,vl,e')
 | Just tl -
let a = length tl
in List.lookup c cases =
 if length vl == a then
   expr prog global (foldl (\e (v,t) - Map.insert v  
t e) env (zip vl (map (subst tenv) tl))) e'

 else
   typeError (arity mismatch in pattern: ++show  
(pretty c)++expected++show a++ argument++(if a == 1 then  else  
s)
 ++ but got [++concat (intersperse ,  (map  
(show . pretty) vl))++])



--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] test-framework success

2009-06-27 Thread Simon Michael
Max - I was thinking about how to drive my new shell tests with your  
framework. I have:


data ShellTest = ShellTest {
 filename ∷ String
,command  ∷ String
,stdin∷ Maybe String
,stdoutExpected   ∷ Maybe String
,stderrExpected   ∷ Maybe String
,exitCodeExpected ∷ Maybe ExitCode
} deriving (Show)

parseShellTest ∷ FilePath → IO ShellTest
runShellTest ∷ ShellTest → IO Bool

I converted to hunit tests with

shellTestToHUnitTest t = filename t ~: do {r ← runShellTest t;  
assertBool  r}


and tied test-framework into my test runner with

main = do
  args ← getArgs
  let (opts,files) = partition ((==-).take 1) args
  hunittests ←  mapM (λf → parseShellTest f = (return ∘  
shellTestToHUnitTest)) files

  withArgs opts $ defaultMain $ concatMap hUnitTestToTests hunittests

With surprisingly little code and pain, the new runner runs my 14  
shell tests, with colored output, in the same time as the old one -  
3.5s on this macbook.


But, I can now add -j8 and get the same results output in.. 0.13s.  
This quite surprised me, and now I want to say: thank you very much! :)


Best,
-Simon

$ time tools/shelltest2 tests/*.test -j8
:tests/eliding-balance.test: [OK]
:tests/missing-real-and-virtual-amt.test: [OK]
:tests/null-accountname-component.test: [OK]
:tests/parens-in-account-name.test: [OK]
:tests/sample-balance-depth.test: [OK]
:tests/sample-balance-o.test: [OK]
:tests/sample-balance.test: [OK]
:tests/unbalanced.test: [OK]
:tests/unicode-account-matching.test: [OK]
:tests/unicode-balance.test: [OK]
:tests/unicode-description-matching.test: [OK]
:tests/unicode-print.test: [OK]
:tests/unicode-register.test: [OK]
:tests/virtual.test: [OK]

 Test Cases   Total
 Passed  14   14
 Failed  00
 Total   14   14

real0m0.132s
user0m0.104s
sys 0m0.104s

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: test-framework success

2009-06-27 Thread Simon Michael

PS - not cabalised, not even committed, but here's my shell test runner for 
folks to play with:

http://joyful.com/repos/hledger/tools/shelltest2.hs

http://joyful.com/repos/hledger/tests/ - test examples

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Rigid type variable error

2009-06-27 Thread Darryn

Thanks for the help previously received, but I still cannot seem to get
on top of this. The types for the constructor K will not resolve and
I'm at a loss to work out what to do with it. If anyone can offer
a further explanation and help I would be very grateful.


My code (File Test5.hs):

{-# LANGUAGE ExistentialQuantification #-}

class A a where
a1 :: a
a2 :: a - a
a3 :: (B b) = b - a

class B b where
b1 :: Int - b

--data Ainst b = I | J (Ainst b) | K b
--  a3 :: (B b, A a) = b - a
--  yet without the constraint on K, K :: b - Ainst b
--  so the above data definition fails. Trying to
--  existentially quantify K below seems to make
--  sense, but also fails ...
data Ainst b = I | J (Ainst b) | (B b) = K b

instance (B b) = A (Ainst b) where
a1 = I
a2 = J
a3 = K -- Reported line of the error

data Binst = Val Int

instance B Binst where
b1 = Val
---

The error from ghci is as follows:

Test5.hs:25:9:
Couldn't match expected type `b' against inferred type `b1'
  `b' is a rigid type variable bound by
  the type signature for `a3' at Test5.hs:7:13
  `b1' is a rigid type variable bound by
   the instance declaration at Test5.hs:16:12
  Expected type: b - Ainst b1
  Inferred type: b1 - Ainst b1
In the expression: K
In the definition of `a3': a3 = K
Failed, modules loaded: none.

Thanks in advance for any help. Apologies if what I am doing is odd or
the answer is obvious, I'm still very new to Haskell.

Darryn.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe