Re: [Haskell-cafe] more gtk help

2013-08-13 Thread briand
On Mon, 12 Aug 2013 14:50:43 +0100
Claude Heiland-Allen cla...@mathr.co.uk wrote:

 Hi Brian,
 
 On 12/08/13 03:52, bri...@aracnet.com wrote:
 ...
  Couldn't match expected type
 ...
Gtk.on Gtk.exposeEvent glCanvas $ \ _ - putStrLn foo
 ...
  I looked up the type of Gtk.on and exposeEvent :
 ...
  on
:: object
   - Signal object callback - callback - IO (ConnectId object)
 ...
 
 I think you have the arguments flipped, try:
 
 Gtk.on glCanvas Gtk.exposeEvent $ \_ - ...
 
 
 As for explaining the types - as I understand it, you have an object and
 a callback, and the Signal associates the object with the callback for a
 specific event type.  The type variables occur more than once in the
 whole type for safety: the right type of callback must be provided for
 the event type, and the object must support the event type too.
 
 

This works

  _ - Gtk.on glCanvas Gtk.exposeEvent $ return True


but not this:

  _ - Gtk.on glCanvas Gtk.exposeEvent fooBar

where

fooBar = 
do putStrLn foo
   return True

so then I thought, aha!, all I need to do is understand the type of return 
True and all will be revealed to me.  Well, it's this:

 Control.Monad.Trans.Reader.ReaderT
   (GHC.Ptr.Ptr Gtk.EExpose) IO Bool

just like the error message says.

Still don't know what that's supposed to be.  I'm having trouble tracking down 

Control.Monad.Trans.Reader.ReaderT




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


[Haskell-cafe] more gtk help

2013-08-11 Thread briand
after getting the entry widget events to work as i wanted, i started looking at 
some other things to do, and my first attempt failed with this :

Couldn't match expected type `Gtk.Signal
(Gtk.Signal self0 (Gtk.EventM Gtk.EExpose 
Bool)) (t0 - IO ())'
with actual type `GtkGL.GLDrawingArea'
In the second argument of `Gtk.on', namely `glCanvas'
In the expression: Gtk.on Gtk.exposeEvent glCanvas
In a stmt of a 'do' block:
  Gtk.on Gtk.exposeEvent glCanvas $ \ _ - putStrLn foo


  Gtk.on Gtk.exposeEvent glCanvas $ putStrLn foo

glCanvas is 

  glCanvas - GtkGL.glDrawingAreaNew glconfig

I looked up the type of Gtk.on and exposeEvent :

exposeEvent
  :: WidgetClass self = Signal self (EventM EExpose Bool)

on
  :: object
 - Signal object callback - callback - IO (ConnectId object)

There are numerous problems starting with the type of 'callback' that I can't 
seem to trace in the documentation.  And I can't figure out why callback is 
repeated...

unfortunately it's not obvious what's going on.  The type of the entry widget 
callback is much simpler, and quite a bit different, so I it's of little help.

I'm having a hard time finding appropriate examples because everything seems to 
use the deprecated convention of on{eventType}, e.g. onExposeEvent or 
onButtonPress.

I was hoping someone could teach me to fish and parse out the type for me and 
provide a simple example.
Just pointing me to up-to-date examples would almost certainly be good enough, 
but I really need to understand the convention here, since I suspect as I try 
to attach events to other widget types I will see these sorts of problems again.


Thanks,

Brian


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


Re: [Haskell-cafe] haskell-gtk entry question

2013-07-27 Thread briand
On Sat, 27 Jul 2013 15:44:44 +0100
Claude Heiland-Allen cla...@mathr.co.uk wrote:

 Perhaps it's a terminology confusion: in GTK, activate for an entry
 means pressing return key.  This program works fine for me, pressing
 return prints the text I entered in the box:
 
 8
 import Graphics.UI.Gtk
 
 main :: IO ()
 main = do
   initGUI
   window - windowNew
   entry - entryNew
   set window [ containerBorderWidth := 10, containerChild := entry ]
   entry `on` entryActivate $ putStrLn = entryGetText entry
   onDestroy window mainQuit
   widgetShowAll window
   mainGUI
 8

yes that's part of the problem - I thought that tabbing through the fields 
should be an activate event.  still I had some other problem, and I'm not 
sure what it was.  however thanks to your example I now have the dialog working 
as it should.

thanks very much !

Brian


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


[Haskell-cafe] haskell-gtk entry question

2013-07-24 Thread briand
Hello all,

This should be simple, and I thought it had it working, but I've broken it and 
can't figure out why.

What I want is to invoke the callback whenever the user activates and entry in 
a dialogbox, so I did both this :

  Gtk.on entry Gtk.entryActivate (boxHandler entry)

(I believe this supercedes the previous method which was onEntryActivate)

and this

  Gtk.on entry Gtk.entryPreeditChanged (boxHandler entry)


however neither method will invoke the callback.  The program compiles and 
works just fine, it's just that the callback never runs.

Thank you,

Brian


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


[Haskell-cafe] opengl type confusion

2013-06-16 Thread briand
This,

wireframe :: Double - Double - Double - IO ()
wireframe wx wy wz = do 
  -- yz plane
  renderPrimitive LineLoop $ do
   vertex $ Vertex3 0.0 0.0 0.0
   vertex $ Vertex3 0.0 wy 0.0
   vertex $ Vertex3 0.0 wy wz
   vertex $ Vertex3 0.0 0.0 wz

produces this:

No instance for (VertexComponent Double)
  arising from a use of `vertex'
Possible fix:
  add an instance declaration for (VertexComponent Double)
In the expression: vertex
In a stmt of a 'do' block: vertex $ Vertex3 0.0 wy 0.0
In the second argument of `($)', namely
  `do { vertex $ Vertex3 0.0 0.0 0.0;
vertex $ Vertex3 0.0 wy 0.0;
vertex $ Vertex3 0.0 wy wz;
vertex $ Vertex3 0.0 0.0 wz }'

and thusly this :-(

Changing the declaration to GLdouble - GLdouble - GLdouble - IO() and using
(0.0::GLdouble) fixes it, and I'm not clear on why it's not automagic.  There 
are many times I see the compiler doing type conversion an numerican arguments 
although sometimes the occasional fracSomethingIntegralorOther is required.

I was hoping for some enlightenment.

Thank you.

Brian


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


Re: [Haskell-cafe] opengl type confusion

2013-06-16 Thread briand
On Sun, 16 Jun 2013 16:15:25 -0400
Brandon Allbery allber...@gmail.com wrote:

 On Sun, Jun 16, 2013 at 4:03 PM, bri...@aracnet.com wrote:
 
  Changing the declaration to GLdouble - GLdouble - GLdouble - IO() and
  using
  (0.0::GLdouble) fixes it, and I'm not clear on why it's not automagic.
   There are many times I see the
 
 
 Haskell never automagics types in that context; if it expects GLdouble,
 it expects GLdouble. Pretending it's Double will not work. It would in
 the specific case that GLdouble were actually a type synonym for Double;
 however, for performance reasons it is not. Haskell Double is not directly
 usable from the C-based API used by OpenGL, so GLdouble is a type synonym
 for CDouble which is.
 
 compiler doing type conversion an numerican arguments although sometimes
  the occasional fracSomethingIntegralorOther is required.
 
 
 I presume the reason the type specification for numeric literals is because
 there is no defaulting (and probably can't be without introducing other
 strange type issues) for GLdouble.
 

What I was thinking about, using a very poor choice of words, was this :


*Main let a = 1
*Main :t a
a :: Integer
*Main let a = 1::Double
*Main a
1.0
*Main :t a
a :: Double
*Main 

so normally 1 would be interpreted as an int, but if I declare 'a' a Double 
then it gets promoted to a Double without me having to call a conversion 
routine explicitly.

That seems automagic to me.

(0.0::GLdouble) works to make the compiler happy.  So it appears to be taking 
care of the conversion automagically.

So maybe a better question, I hope, is:

How can I simply declare 0.0 to be (0.0::GLdouble) and have the functional call 
work.  Doesn't a conversion have to be happening, i.e. shouldn't I really have 
to do (realToFrac 0.0) ?

Brian


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


Re: [Haskell-cafe] opengl type confusion

2013-06-16 Thread briand
On Sun, 16 Jun 2013 22:19:22 +0100
Tom Ellis tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:

 On Sun, Jun 16, 2013 at 01:03:48PM -0700, bri...@aracnet.com wrote:
  wireframe :: Double - Double - Double - IO ()
  wireframe wx wy wz = do 
-- yz plane
renderPrimitive LineLoop $ do
 vertex $ Vertex3 0.0 0.0 0.0
 vertex $ Vertex3 0.0 wy 0.0
 vertex $ Vertex3 0.0 wy wz
 vertex $ Vertex3 0.0 0.0 wz
 [...]
  
  No instance for (VertexComponent Double)
arising from a use of `vertex'
 [...]
  
  Changing the declaration to GLdouble - GLdouble - GLdouble - IO() and 
  using
  (0.0::GLdouble) fixes it
 
 Vertex3 takes three arguments, all of which must be of the same instance of
 VertexComponent.  Specifying GLdoubles in the signature of wireframe
 specifies the types in the last three calls to Vertex3, but (0.0 ::
 GLdouble) is still requried on the first to fix the type there.  How else
 could the compiler know that you mean 0.0 to be a GLdouble and not a
 GLfloat?
 
 Tom
 


it's curious that 

(0.0::GLdouble) 0.0 0.0 

is good enough and that 

(0.0::GLdouble) (0.0::GLdouble) (0.0::GLdouble)

is not required.  I suspect that's because, as you point out, they all have to 
be the same argument and ghc is being smart and saying if the first arg _must_ 
be GLdouble (because I'm explicitly forcing the type), then the rest must be 
too.

Meanwhile 4.3.4 about the default is quite interesting. Didn't know about that 
:-)

Thanks very much for the responses !

Brian



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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-03 Thread briand
On Mon, 03 Jun 2013 19:16:08 +
silvio silvio.fris...@gmail.com wrote:

 Hi everyone,
 
 Every time I want to use an array in Haskell, I find myself having to 
 look up in the doc how they are used, which exactly are the modules I 
 have to import ... and I am a bit tired of staring at type signatures 
 for 10 minutes to figure out how these arrays work every time I use them 
 (It's even worse when you have to write the signatures). I wonder how 
 other people perceive this issue and what possible solutions could be.

My opinion, it's every bit as bad you say it is...
Not a clue as to what can be done about it.

Probably yet another vector module.





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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-03 Thread briand
On Mon, 3 Jun 2013 23:19:38 -0400
Clark Gaebel cgae...@uwaterloo.ca wrote:

 That's absolutely true. Wrappers around vector for your multidimensional
 access is probably best, but Vectors of Vectors are usually easier.
 
 But again, you're right. Multidimensional access is a pain. If it's a
 matrix of numerical values, you could take a look at 'hmatrix'.

or repa


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


Re: [Haskell-cafe] Concurrency performance problem

2013-03-04 Thread briand
On Mon, 4 Mar 2013 20:39:43 +0100
Łukasz Dąbek sznu...@gmail.com wrote:

 Thank you for your help! This solved my performance problem :)
 

do you have a link to the new code ?

it should be very instructive to see the differences.

Brian


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


Re: [Haskell-cafe] Trouble installing and using Chart/cairo on windows 7

2013-03-03 Thread briand
On Sun, 3 Mar 2013 19:58:37 -0500
Brent Yorgey byor...@seas.upenn.edu wrote:

 
 Good access to fonts and font metrics is the kicker.  Otherwise I'd
 say to switch to using diagrams as a backend, hence getting a whole
 bunch of actual backends for free.  I would love to see development of
 some good Haskell font packages -- maybe it would even make a good
 GSoC project?  Unfortunately I don't know enough about it to even know
 what would be involved, or how much work it would be.
 

I assume that to use diagram the font package would have to be a vector font 
system, or could bit-mapped fonts be used ?


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


[Haskell-cafe] ~ operator ?

2013-02-18 Thread briand
Hi all,

I was creating bigger uncurries which I am simply extending from an existing 
uncurry I found some where, e.g.

uncurry4 :: (a - b - c - d - e) - ((a, b, c, d) - e)
uncurry4 f ~(a,b,c,d) = f a b c d

when I realized, what's the ~ for ?

I've only been able to find a partial explanation that it involves preserving 
laziness, or something, maybe ?

I was hoping someone could enlighten me.

Thanks

Brian


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


Re: [Haskell-cafe] ~ operator ?

2013-02-18 Thread briand
On Mon, 18 Feb 2013 19:13:13 +
Mateusz Kowalczyk fuuze...@fuuzetsu.co.uk wrote:

 On 18/02/13 19:02, bri...@aracnet.com wrote:
  Hi all,
  
  I was creating bigger uncurries which I am simply extending from an 
  existing uncurry I found some where, e.g.
  
  uncurry4 :: (a - b - c - d - e) - ((a, b, c, d) - e)
  uncurry4 f ~(a,b,c,d) = f a b c d
  
  when I realized, what's the ~ for ?
  
  I've only been able to find a partial explanation that it involves 
  preserving laziness, or something, maybe ?
  
  I was hoping someone could enlighten me.
  
  Thanks
  
  Brian
  
  
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
  
 
 [1] explains it in section 4.4 — ‘Lazy patterns’.
 
 [1] - http://www.haskell.org/tutorial/patterns.html
 

how strange - I was sure I looked through the tutorial...

Thanks Mateusz and Patrick.

Brian



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


Re: [Haskell-cafe] performance question

2013-02-12 Thread briand
On Tue, 12 Feb 2013 15:57:37 -0700
Nicolas Bock nicolasb...@gmail.com wrote:

   Here is haskell version that is faster than python, almost as fast as c++.
  You need to install bytestring-lexing package for readDouble.


I was hoping Branimir could comment on how the improvements were allocated.

how much is due to text.regex.pcre (which looks to be a wrapper to libpcre) ?

how much can be attributed to using data.bytestring ?

you have to admit, it's amazing how well a byte-compiled, _dynamically typed_ 
interpreter can do against an actualy native code compiler.  Can't regex be 
done effectively in haskell ?  Is it something that can't be done, or is it 
just such minimal effort to link to pcre that it's not worth the trouble ?


Brian

  import Text.Regex.PCRE
  import Data.Maybe
  import Data.Array.IO
  import Data.Array.Unboxed
  import qualified Data.ByteString.Char8 as B
  import Data.ByteString.Lex.Double (readDouble)
 
  strataBounds :: UArray Int Double
  strataBounds = listArray (0,10) [ 0.0, 1.0e-8, 1.0e-7, 1.0e-6, 1.0e-5,
  1.0e-4, 1.0e-3, 1.0e-2, 1.0e-1, 1.0, 2.0 ]
 
  newStrataCounts :: IO(IOUArray Int Int)
  newStrataCounts = newArray (bounds strataBounds) 0
 
  main = do
  l - B.getContents
  let a = B.lines l
  strataCounts - newStrataCounts
  n - calculate strataCounts a 0
  let
  printStrataCounts :: IO ()
  printStrataCounts = do
  let s = round $ sqrt (fromIntegral n::Double) :: Int
  printf read %d matrix elements (%dx%d = %d)\n n s s n
  printStrataCounts' 0 0
  printStrataCounts' :: Int - Int - IO ()
  printStrataCounts' i total
  | i  (snd $ bounds strataBounds) = do
  count - readArray strataCounts i
  let
  p :: Double
  p = (100.0*(fromIntegral count) ::
  Double)/(fromIntegral n :: Double)
  printf [%1.2e, %1.2e) = %i (%1.2f%%) %i\n (strataBounds
  ! i) (strataBounds ! (i+1))
  count p
  (total + count)
  printStrataCounts' (i+1) (total+count)
  | otherwise = return ()
  printStrataCounts
 
  calculate :: IOUArray Int Int - [B.ByteString] - Int - IO Int
  calculate _ [] n = return n
  calculate counts (l:ls) n = do
  let
  a = case getAllTextSubmatches $ l =~ B.pack matrix.*=
  ([0-9eE.+-]+)$ :: [B.ByteString] of
  [_,v] - Just (readDouble v) :: Maybe (Maybe
  (Double,B.ByteString))
  _ - Nothing
  b = (fst.fromJust.fromJust) a
  loop :: Int - IO()
  loop i
  | i  (snd $ bounds strataBounds) =
  if (b = (strataBounds ! i))  (b  (strataBounds !
  (i+1)))
  then do
  c - readArray counts i
  writeArray counts i (c+1)
  else
  loop (i+1)
  | otherwise = return ()
  if isNothing a
  then
  calculate counts ls n
  else do
  loop 0
  calculate counts ls (n+1)
 
 
  --
  From: nicolasb...@gmail.com
  Date: Fri, 8 Feb 2013 12:26:09 -0700
  To: haskell-cafe@haskell.org
  Subject: [Haskell-cafe] performance question
 
  Hi list,
 
  I wrote a script that reads matrix elements from standard input, parses
  the input using a regular expression, and then bins the matrix elements by
  magnitude. I wrote the same script in python (just to be sure :) ) and find
  that the python version vastly outperforms the Haskell script.
 
  To be concrete:
 
  $ time ./createMatrixDump.py -N 128 | ./printMatrixDecay
  real0m2.655s
  user0m2.677s
  sys 0m0.095s
 
  $ time ./createMatrixDump.py -N 128 | ./printMatrixDecay.py -
  real0m0.445s
  user0m0.615s
  sys 0m0.032s
 
  The Haskell script was compiled with ghc --make printMatrixDecay.hs.
 
  Could you have a look at the script and give me some pointers as to where
  I could improve it, both in terms of performance and also generally, as I
  am very new to Haskell.
 
  Thanks already,
 
  nick
 
 
  ___ 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


[Haskell-cafe] hxt pickling question

2013-01-24 Thread briand
Hi,

Trying to understand how to write a document using a pickler but I can't make 
sense of the types.  

From the example:

 runX ( xunpickleDocument xpSeason
   [ withValidate no
   , withTrace 1
   , withRemoveWS yes
   , withPreserveComment no
   ] simple2.xml
   
 processSeason
   
 xpickleDocument   xpSeason
   [ withIndent yes
   ] new-simple2.xml
   )

So all I want to do is pickle a value directly instead of reading the value 
from a document.  I expected to do something like:

runX (someHXTPicklingFunction myValue

  xpickleDocument ...)


but I can't seem to figure out what someHXTPicklingFunction should be, it's 
certainly nothing obvious like pickleDoc, because that generates the wrong 
value.

Seems like I probably have a much more fundamental problem in that I really 
don't understand how the arrow part of this little example really works, but I 
was kind of hoping that doing something simple like this might shed some 
light on that.  And then was immediately stuck in type hell.

   
Thanks,

Brian


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


Re: [Haskell-cafe] hxt pickling question

2013-01-24 Thread briand
On Thu, 24 Jan 2013 17:05:15 +0100
Erik Hesselink hessel...@gmail.com wrote:

 There's showPickled [0] and unpickleDoc [1], maybe those help?
 

Thank you , they help a lot :-)  I was stuck looking in 
Text.XML.HXT.Arrow.Pickle for the answer and got lost trying to decipher 
IOStateArrow s a XmlTree and runX.

It's odd that there does not seem to be a way to use the example so that a tree 
can be written directly to a file.

  xpickleDocument :: PU a - SysConfigList - String - IOStateArrow s a 
XmlTreeSource

  store an arbitray value in a persistent XML document 

Except there doesn't seem to be a way to pass that value into xpickleDocument 
without reading a document first using xunpickleDocument.

Thanks again.

Brian

 Erik
 
 [0] 
 http://hackage.haskell.org/packages/archive/hxt/latest/doc/html/Text-XML-HXT-Arrow-Pickle-Xml.html#v:showPickled
 [1] 
 http://hackage.haskell.org/packages/archive/hxt/latest/doc/html/Text-XML-HXT-Arrow-Pickle-Xml.html#v:unpickleDoc
 
 On Thu, Jan 24, 2013 at 4:40 PM,  bri...@aracnet.com wrote:
  Hi,
 
  Trying to understand how to write a document using a pickler but I can't 
  make sense of the types.
 
  From the example:
 
   runX ( xunpickleDocument xpSeason
 [ withValidate no
 , withTrace 1
 , withRemoveWS yes
 , withPreserveComment no
 ] simple2.xml
   
   processSeason
   
   xpickleDocument   xpSeason
 [ withIndent yes
 ] new-simple2.xml
 )
 
  So all I want to do is pickle a value directly instead of reading the value 
  from a document.  I expected to do something like:
 
  runX (someHXTPicklingFunction myValue

xpickleDocument ...)
 
 
  but I can't seem to figure out what someHXTPicklingFunction should be, it's 
  certainly nothing obvious like pickleDoc, because that generates the wrong 
  value.
 
  Seems like I probably have a much more fundamental problem in that I really 
  don't understand how the arrow part of this little example really works, 
  but I was kind of hoping that doing something simple like this might shed 
  some light on that.  And then was immediately stuck in type hell.
 
 
  Thanks,
 
  Brian
 
 
  ___
  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] Memoization of functions

2011-09-06 Thread briand
On Tue, 06 Sep 2011 15:16:09 -0400
Michael Orlitzky mich...@orlitzky.com wrote:

 I'm working on a program where I need to compute a gajillion (171442176)
 polynomials and evaluate them more than once. This is the definition of
 the polynomial, and it is expensive to compute:
 
  polynomial :: Tetrahedron - (RealFunction Point)
  polynomial t =
  sum [ (c t i j k l) `cmult` (beta t i j k l) | i - [0..3],
 j - [0..3],
 k - [0..3],
 l - [0..3],
 i + j + k + l == 3]
 
 Currently, I'm storing the polynomials in an array, which is quickly
 devoured by the OOM killer. This makes me wonder: how much memory can I
 expect to use storing a function in an array? Is it possible to save
 some space through strictness? Does that question even make sense?
 

it's not clear what the relation to your final result is, e.g. can you can 
computer partial values and then store them ?  or are you having to calculate 
all 171442176 values and then do further computation with those values ?

if you need to store the results of the polynomials and then use them for 
further computation, well then it would seem that you're out of luck.

unboxing is likely to be your best friend.

in the event that unboxed arrays would help, I highly recommend repa.

Brian


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


Re: [Haskell-cafe] Data.Time

2011-06-27 Thread briand
On Mon, 27 Jun 2011 11:15:28 +0300
Yitzchak Gale g...@sefer.org wrote:

 
 The biggest shortcoming, in my opinion, is that the documentation
 assumes that the reader is very familiar with the Haskell type
 system, and with viewing type signatures and instance lists as an
 integral and central part of the documentation.
 
 In particular, Haskell's standard numeric type classes and the
 conversion functions between them play a central role in the API
 of Data.Time. But you wouldn't realize that unless you have read
 the type signatures and instance lists in the Haddocks very
 carefully, and have thought about it for a while.

This is exactly right.

 
 Another problem, as Malcolm pointed out, is that because of the
 sheer size of the library, a quick-start guide for the common
 cases would be extremely helpful for newcomers.

That would be very, very helpful.  I had a few working examples things were 
much better.  Finding a starting place, any starting place, proved to be quite 
elusive.  Also the fact that asking for the current time traps you in IO hell, 
doesn't help, although it's clear that it should be that way.

Brian

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


[Haskell-cafe] location of IEEE Viz code ?

2011-06-12 Thread briand
Hi,

I hate to even ask this because the answer is probably staring me in the face.

This trac page 

http://hackage.haskell.org/trac/PolyFunViz/wiki/IEEEVisCode

talks about the code being available through darcs but I can't seem to put my 
hands on the http address I would need to pull the code.

This is all relating to the paper, Huge Data but Small Programs: Visualization 
Design via Multiple Embedded DSLs.

I was wondering if anyone has accessed it and/or knows where it's hiding.

Thank you,

Brian


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


Re: [Haskell-cafe] location of IEEE Viz code ?

2011-06-12 Thread briand
On Sun, 12 Jun 2011 21:25:22 +0100
Malcolm Wallace malcolm.wall...@me.com wrote:

  http://hackage.haskell.org/trac/PolyFunViz/wiki/IEEEVisCode
  
  talks about the code being available through darcs but I can't seem to put 
  my hands on the http address I would need to pull the code.
  
  This is all relating to the paper, Huge Data but Small Programs: 
  Visualization Design via Multiple Embedded DSLs.
 
 http://www.cs.york.ac.uk/fp/darcs/polyfunviz/
 
 I can't recall the exact state of the repository; it is likely that some of 
 it may no longer build with newer versions of ghc and/or OpenGL.
 

Hi Malcolm,

Very minor changes:

darcs diff ByteStringExtras.hs
8c8,9
 import Data.ByteString.Base
---
 import Data.ByteString.Unsafe
 import Data.ByteString

To make MViewer work :-)

Brian

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


Re: [Haskell-cafe] How do you test a parser?

2011-06-11 Thread briand
On Sat, 11 Jun 2011 10:34:47 -0700
Alexander Solla alex.so...@gmail.com wrote:

 On Sat, Jun 11, 2011 at 10:06 AM, Sean Perry sha...@speakeasy.net wrote:
 
  Choices, choices.
 
  The first one is to use unit tests. Look at the grammar and make sure the
  obvious stuff fails or succeeds. a + b, a :+ b, etc. You can do this at
  the Haskell level with parser objects.
 
  Next you can write small samples to test things the unit tests did not.
  Compare the output to known results. There are numerous examples of this in
  the open source world you can either reuse or crib from.
 
 
 Don't just test the obvious things.   If the parse tree is truly a tree,
 it is an initial algebra and amenable to case analysis as an initial
 algebra.  In other words, you can do a proof by induction, just by checking
 all the base cases.

Wouldn't also be reasonable for the test cases to be generated from the grammar 
automagically ?  Seems much more useful than attempting to do it by hand.  
Seems like something which would have already been done, i.e. there's already a 
tool out there that does that ?

Brian

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


[Haskell-cafe] best way to use ghc-7.0 under debian stable

2011-06-09 Thread briand
Hi All,

Currently debian stable installs ghc 6.12.1.

I'd like to use the latest version of repa which is built on ghc 7.0, and my 
attempts to placate cabal's complaints about the installation of various 
packages isn't going anywhere.

It's not obvious to me that there's an advantage to using debian for ghc if I 
want to stay on the latest ghc to support various packages.

I'm wondering what the best way to maintain the latest ghc while using debian 
stable.

Should I abandon the ghc debian package and install the haskell-platform ?  
Should I simply build ghc 7.0 independently ?  The advantage of building ghc 
myself would of course be the ability to incorporate latest patches etc, and 
that seems like a good way to go.

Any advice appreciated.

Thanks,


Brian

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


Re: [Haskell-cafe] Accelerate package (CUDA). How to actually create an array?

2011-05-17 Thread briand
On Mon, 16 May 2011 20:33:12 +0400
Grigory Sarnitskiy sargrig...@ya.ru wrote:

 Hello!
 
 I'm probing CUDA with Haskell, accelerate package to be exact. Sound stupid, 
 but I couldn't find how to actually construct an array, for example Vector 
 Float.
 
 There is quite a number of examples provided with the package, but they seem 
 not simple enough for me just to start.
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

Have a fish :-)


import Data.Array.Repa as A
import Data.Array.Repa.Index
import Data.Array.Repa.Shape as AS

newArray :: Int - Array DIM2 Double
newArray n = 
--A.fromList ((AS.shapeOfList [n, n])::(DIM2)) ((Prelude.map fromIntegral 
[1..n*n])::[Double])
A.fromList (AS.shapeOfList [n, n]) (Prelude.map fromIntegral [1..n*n])

main = do
  let x = newArray 5
  let y = newArray 5
  let z = A.zipWith(+) x y
  putStrLn $ show x
  putStrLn $ show y
  putStrLn $ show z

*Main main
[1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0,10.0,11.0,12.0,13.0,14.0,15.0,16.0,17.0,18.0,19.0,20.0,21.0,22.0,23.0,24.0,25.0]
[1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0,10.0,11.0,12.0,13.0,14.0,15.0,16.0,17.0,18.0,19.0,20.0,21.0,22.0,23.0,24.0,25.0]
[2.0,4.0,6.0,8.0,10.0,12.0,14.0,16.0,18.0,20.0,22.0,24.0,26.0,28.0,30.0,32.0,34.0,36.0,38.0,40.0,42.0,44.0,46.0,48.0,50.0]
*Main 

I can't remember what Prelude.map collided with.

Brian


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


[Haskell-cafe] why doesn't ghc give you a type signature that works ?

2011-05-17 Thread briand
for example:

I will ask the glorious compiler, and it says:

*Main :t calcFFT
calcFFT
  :: (Math.FFT.Base.FFTWReal r) =
 V.Vector (Complex r) - V.Vector (Complex r)

I then put the signature in my code, reload it, and:

  Not in scope: type constructor or class `Math.FFT.Base.FFTWReal'


It seems very strange to me that the fully qualified module name doesn't work, 
nor does any combination thereof, e.g. FFT.FFTWReal, FFT.Base.FFTWReal, etc...

I'm importing FFT as:

  import qualified Math.FFT as FFT

I'm not sure if that causes the problem.

Generally speaking this happens to me quite a lot, and I've never tried to 
understand what's going on, because the signature is not required.  I've 
decided to try now :-)

Obviously I'll need some help.

Thanks,

Brian

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


[Haskell-cafe] repa Shape help

2011-05-08 Thread briand
Howdy,

as usual, the haskell type system complete defeats me in the simplest of 
applications:

import Data.Array.Repa as A
import Data.Array.Repa.Index
import Data.Array.Repa.Shape as AS

main = do
  let x = A.fromList (AS.shapeOfList [2, 2]) ([1.0, 2.0, 3.0, 4.0]::[Double])
  putStrLn $ show x

test_repa.hs:10:13:
Ambiguous type variable `sh' in the constraint:
  `Shape sh' arising from a use of `show' at test_repa.hs:10:13-18
Probable fix: add a type signature that fixes these type variable(s)
Failed, modules loaded: none.

After much staring at the type signatures I finally figured out that adding a 
type annotation to x of :

  :: Array DIM2 Double

would fix the problem, but I'm not completely clear as to why.

after all fromList is typed:

(Shape sh, Elt a) = sh - [a] - Array sh a

Since it knows [a] is [Double] and sh must be - well I'm not really clear on 
what sh is supposed to be.  therein lies my problem.  Although it does seem 
that sh can be darn near anything, which is probably why it was ambiguous.

At one point I had tried something like (2 :. 2) and got a whole host of errors 
for that too, except that DIM2 is defined in exactly that way, so it's not at 
all obvious why that didn't work.

I was hoping someone could clarify on what's going on.


Thanks,

Brian


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


Re: [Haskell-cafe] ANN: Newt - command-line template instantiation tool library

2011-05-08 Thread briand
On Sun, 8 May 2011 16:23:59 -0700
Rogan Creswick cresw...@gmail.com wrote:

 Newt scans the input (either a file, directory or stdin) for tags
 marked with tagName [1], then replaces those entries with
 values specified on the command line, producing either a new file,
 modifying the input template in place (--inplace), writing to stdout,
 or writing to a directory.

This is a useful tool !

I would like to suggest allowing customization of the syntax to indicate a tag, 
e.g. {# #} instead of   (You just knew someone was going to say that, 
right ? :-)

I only mention this in the hopes that it still early enough for you to write 
the code in such a way to allow this even if you don't implement it right away.


Brian

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


Re: [Haskell-cafe] writing to a fifo when the reader stops reading

2011-03-14 Thread briand
On Mon, 14 Mar 2011 02:33:13 -0400
Brandon S Allbery KF8NH allber...@gmail.com wrote:

 -BEGIN PGP SIGNED MESSAGE-
 Hash: SHA1
 
 On 3/13/11 03:16 , bri...@aracnet.com wrote:
  ghc: fdWriteBuf: resource vanished (Broken pipe)
  
  which make sense, sort of.  I write a value, let's say 10, and the
  reader reads it.  It's the last value so it closes the fifo.
  
  Now there's nothing reading, so when I get to threadWaitWrite, I
  would expect the program to wait, just as it does when it starts up
  and there is no reader.
 
 FIFOs don't work that way; like a regular pipe, once all readers go
 away it doesn't work any more.  You need to open it read-write
 initially to keep a reader around.  Haskell has no control over
 this:  it's how they're defined to work.

ok,  I wanted to make sure that I wasn't missing something on the
Haskell side.

 
 In general, trying to use a FIFO like an AF_UNIX socket is a mistake.
 


and using a socket doesn't really make sense because everything is
running on the same host, always will be, and using sockets will
unnecessarily complicate things.  although it's not that bad and works
really well.

I'll go figure out a different strategy.

Thank you,

Brian

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


[Haskell-cafe] writing to a fifo when the reader stops reading

2011-03-12 Thread briand
Hi all,

here's the code:

writer =
  do threadDelay 10
 threadWaitWrite fd
 fdWrite fd ((show x) ++ \n)
 writer fd (x+1)


pretty simple, it just keeps writing.  What happens though is that,
eventually, the reader goes away, i.e. closes the fifo.

When that happens I get:

ghc: fdWriteBuf: resource vanished (Broken pipe)


which make sense, sort of.  I write a value, let's say 10, and the
reader reads it.  It's the last value so it closes the fifo.

Now there's nothing reading, so when I get to threadWaitWrite, I would
expect the program to wait, just as it does when it starts up and there
is no reader.

looking for some guidance.

Thank you,


Brian



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


Re: [Haskell-cafe] [SOLVED] why is ghci trying to load hsc file ??

2011-02-28 Thread briand
On Mon, 28 Feb 2011 02:58:58 +
Felipe Almeida Lessa felipe.le...@gmail.com wrote:

 On Sun, Feb 27, 2011 at 6:48 AM, by way of bri...@aracnet.com
 bri...@aracnet.com wrote:
  the binding-DSL examples do NOT use the above PRAGMA anywhere in the
  code.
 
 Probably they have
 
   Extensions:  ForeignFunctionInterface
 
 on their .cabal file.
 

as I do, hence the reason for my confusion :-(

Something's not working right and I can't begin to guess why not.

I had to put the actual pragma in my .hsc file to make things work, and
now it works.



Brian

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


Re: [Haskell-cafe] [SOLVED] why is ghci trying to load hsc file ??

2011-02-27 Thread briand
On Sat, 26 Feb 2011 22:42:15 -0700
Chris Smith cdsm...@gmail.com wrote:

 On Sat, 2011-02-26 at 21:36 -0800, bri...@aracnet.com wrote:
  [1 of 2] Compiling Bindings.HDF5( dist/build/Bindings/HDF5.hs,
  interpreted ) *** Parser:
  
  src/Bindings/HDF5.hsc:49:8: parse error on input `import'
 
 So it's in HDF5.hs ultimately, but LINE directives are telling it to
 report a different location.
 
  HDF5.hs file has LINE scattered throughout, but they are in
  comments:
  
  {-# LINE 15 src/Bindings/HDF5.hsc #-}
 
 Those {-# ... #-} things are pragmas.  As far as the language spec
 goes they are comments, but actually, compilers read them and
 interpret their contents.  In this case, it causes the compiler to
 report a different location for errors.
 
  regardless, there is NO LINE 49 directive, and the HDF5.hs file is
  blank on line 49.
 
 Line 49 of HDF5.hs doesn't matter.  What's on line 49 of the hsc file?
 
 If you don't want to debug using the hsc file (which is the way this
 is designed), you'll have to find the LINE directive in the .hs file
 nearest to (but before) 49, and count lines from there.
 


argh !

this is needed in the .hs file generated by the .hsc.  It's not good
enough to put it in the source code which uses the library :

{-# LANGUAGE ForeignFunctionInterface #-}

what I don't understand is why the hsc processing and/or cabal build
doesn't automagically handle this.  maybe a ghc version thing ?  I'm
using 6.12.1.

the binding-DSL examples do NOT use the above PRAGMA anywhere in the
code.


Brian

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


[Haskell-cafe] why is ghci trying to load hsc file ??

2011-02-26 Thread briand
Howdy,

I worked out a small hdf5 binding using cabal and bindings-DSL and
sqlite3 as my example.

Time to try it !

ghci -idist/build/ dist/build/Bindings/HDF5.o -lhdf5 -lhdf5_hl
hdf5_pkg_test.hs


GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading object (static) dist/build/Bindings/HDF5.o ... done
Loading object (dynamic) hdf5 ... done
Loading object (dynamic) hdf5_hl ... done
final link ... done
[1 of 2] Compiling Bindings.HDF5( dist/build/Bindings/HDF5.hs,
interpreted )

src/Bindings/HDF5.hsc:49:8: parse error on input `import'
Failed, modules loaded: none.


Huh ?  Why is it trying to read HDF5.hsc ??  What's even more
interesting is that line 49 of that file doesn't have an import on it,
so something is fubar.

No idea how this could be happening.  I've included a copy of my cabal
file.

BTW. I have to specify the hdf5 libraries, i.e. libhdf5 and libhdf5_hl
on the command line. It seems like the build process should have taken
care of that in some way, maybe... ?  Certainly when I use something
like sqlite3, I'm not specifying libsqlite3 on the command line.

Thanks,

Brian


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


Re: [Haskell-cafe] why is ghci trying to load hsc file ??

2011-02-26 Thread briand
On Sat, 26 Feb 2011 18:18:27 -0800 (PST)
Brandon Moore brandon_m_mo...@yahoo.com wrote:

 I assume there's a LINE directive in the file it's actually reading.
 Run ghci with -v to see what file it's actually trying to read.
 
 
   

Here's the relevant output with -v flag:


compile: input file dist/build/Bindings/HDF5.hs
*** Checking old interface for main:Bindings.HDF5:
[1 of 2] Compiling Bindings.HDF5( dist/build/Bindings/HDF5.hs,
interpreted ) *** Parser:

src/Bindings/HDF5.hsc:49:8: parse error on input `import'


This is very weird.

HDF5.hs file has LINE scattered throughout, but they are in comments:

{-# LINE 15 src/Bindings/HDF5.hsc #-}

or are they ?  I assumed the purpose of this was line # annotation to
let you know where the line in the .hs file comes from in the .hsc
file.

regardless, there is NO LINE 49 directive, and the HDF5.hs file is
blank on line 49.

The first line with import (@ 165) is this :

foreign import ccall H5Dcreate2 c'H5Dcreate2
  :: CInt - CString - CInt - CInt - CInt - CInt - CInt - IO

I'm trying to figure out if that's legal syntax.

Very strange.  Reporting errors on lines that don't exist makes it
harder to debug :-(

Brian

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


[Haskell-cafe] best way to deal with #defines when developing ffi's

2011-02-22 Thread briand
Hi all,

I'm working on an FFI and as usual there are lots of defines in
the header files.

What's the best way to make these available to the haskell code ?
Ideally it could be done automagically, or at least pseudo-magically so
that keeping up with changes to the .h wouldn't be too painful.

I'm talking about simple constant defines, nothing tricky like
structures or similar.

Thanks,

Brian

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


[Haskell-cafe] command line options using ghc -e

2010-12-26 Thread briand
Hi,


for example :

  ghc -e main foo.hs these should be treated as args for argv

I'm wondering if there is a magic option to indicate that everything
after this option is an arg option.

Thanks

Brian

P.S. yes I know about :main args in ghci.


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


[Haskell-cafe] global, modifiable variable for debugging

2010-12-26 Thread briand
Hi,

I have a program with a debug flag in it (Strangely I've yet to be
able to write bug-free code).  I'd like to change the state of the
debug flag based on command line args.

I looked at IOVar but that would cause all the pure procedures to get
swallowed by the IO Monad.

Is a better way to get this behavior ?

Thanks,

Brian


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


[Haskell-cafe] searching haskell-cafe ?

2010-09-19 Thread briand
is there a way to search the haskell-cafe list.

I found a potential link on the haskell wiki, but the link is busted.

Didn't see anything on the haskell-cafe mailing list page.

Thanks,

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


[Haskell-cafe] cairo rendered to screen examples

2010-08-08 Thread briand
I've been running around the gtk2hs web site and can't seem to find the
actual code (I did find the cairo blog, with examples but no code).

Can some kind soul post a link ?

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


Re: [Haskell-cafe] cairo rendered to screen examples

2010-08-08 Thread briand
On Sun, 8 Aug 2010 11:13:33 -0700
bri...@aracnet.com wrote:

 I've been running around the gtk2hs web site and can't seem to find
 the actual code (I did find the cairo blog, with examples but no
 code).
 
 Can some kind soul post a link ?
 

and here you go:

http://code.haskell.org/gtk2hs/cairo/demo/

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


[Haskell-cafe] gkt2hs seg fault issue

2010-08-08 Thread briand
I reported a seg-fault in chart a while back.

so I was experimenting with cairo and rendering to to the screen, which
if my understanding is correct, uses gtk.  Certainly looks like it.

So I compiled the cairo example Drawing.hs and that worked fine.

I then tried running the example from ghci, i.e. loading it and typing
main.

I get a seg-fault when it exits:

Ok, modules loaded: Main.
*Main main
Loading package array-0.3.0.0 ... linking ... done.
Loading package bytestring-0.9.1.5 ... linking ... done.
Loading package filepath-1.1.0.3 ... linking ... done.
Loading package old-locale-1.0.0.2 ... linking ... done.
Loading package old-time-1.0.0.3 ... linking ... done.
Loading package unix-2.4.0.0 ... linking ... done.
Loading package directory-1.0.1.0 ... linking ... done.
Loading package process-1.0.1.2 ... linking ... done.
Loading package time-1.1.4 ... linking ... done.
Loading package random-1.0.0.2 ... linking ... done.
Loading package haskell98 ... linking ... done.
Loading package mtl-1.1.0.2 ... linking ... done.
Loading package cairo-0.11.0 ... linking ... done.
Loading package containers-0.3.0.0 ... linking ... done.
Loading package glib-0.11.0 ... linking ... done.
Loading package gio-0.11.0 ... linking ... done.
Loading package pretty-1.0.1.1 ... linking ... done.
Loading package pango-0.11.0 ... linking ... done.
Loading package gtk-0.11.0 ... linking ... done.
*Main Segmentation fault

I included all the messages in case someone knows that one of the
libraries is out of date and could be the source of the problem.

Is it to be expected that it would seg-fault under ghci ??

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


Re: [Haskell-cafe] Re: gkt2hs seg fault issue

2010-08-08 Thread briand
On Mon, 09 Aug 2010 11:09:40 +0800
Andy Stewart lazycat.mana...@gmail.com wrote:

 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com writes:
 
  On 9 August 2010 09:44, Andy Stewart lazycat.mana...@gmail.com
  wrote:
  Which ghc version?
 

The Glorious Glasgow Haskell Compilation System, version 6.12.1

So just run gdb on ghci to see what is happening ?

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


Re: [Haskell-cafe] Re: Haskell in Industry

2010-08-06 Thread briand
On Thu, 5 Aug 2010 21:58:15 -0500
Tom Hawkins tomahawk...@gmail.com wrote:

 Good, we need more functional programmers actually solving real
 problems.  But please put your skills to work in an industry other
 than investment banking.

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


Re: [Haskell-cafe] Chart package segfaults when rendering to window

2010-07-27 Thread briand
On Mon, 26 Jul 2010 21:54:16 -0700
Thomas DuBuisson thomas.dubuis...@gmail.com wrote:

 Can you boil this down to some simple example code?  Are you using a
 recent version of Chart?  And your definition of latest gtk2hs is
 11, right?  How about your gtk+ C library, it what? 2.20?
 

I can run any of the examples from the home page that render to screen.

the AM chart is the one I'm using.

BTW, the AM chart has a bug.  It does not include the proper color
modules and needs a (opaque color) instead of just color.

gtk2hs is 11

gtk+ C library appars to be (debian package) 2.20.1


 
  I was wondering if anybody has been using Chart and may have seen
  the same thing.
 
 Nope, not me.

Yep, figured I'd be suffering alone.

Brian

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


[Haskell-cafe] Chart package segfaults when rendering to window

2010-07-26 Thread briand
Seems to be ok rendering to png files.

I was wondering if anybody has been using Chart and may have seen the
same thing.

I'm running ghc 6.12.1 and the latest and greatest gtk2hs :-)

Thanks,

Brian

p.s. the amplitude modulation
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RE: Design for 2010.2.x series Haskell Platform site (Don Stewart)

2010-07-17 Thread briand
On Sat, 17 Jul 2010 18:02:05 -0400
Brandon S Allbery KF8NH allb...@ece.cmu.edu wrote:

 -BEGIN PGP SIGNED MESSAGE-
 Hash: SHA1
 
 On 7/17/10 13:23 , Christopher Done wrote:
  On 17 July 2010 18:18, Niemeijer, R.A. r.a.niemei...@tue.nl wrote:
  Screenshot: http://imgur.com/9LHvk.jpg
  Live version:
  http://dl.dropbox.com/u/623671/haskell_platform_redesign/index.htm
  
  O, I like it! Nice one for building it. Would you consider
  doing a design for the Haskell web site based on this template?
  (MediaWiki, remember)
 
 +1
 

+1 also

but why is linux cross-eyed ? :-)

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


Re: [Haskell-cafe] Re: Please report any bug of gtk2hs-0.11.0!

2010-07-14 Thread briand
On Wed, 14 Jul 2010 21:05:35 +0800
Andy Stewart lazycat.mana...@gmail.com wrote:


  Where's the demo directory ?!
 Sorry, we forgot add demo in .cabal file when we released
 gtk2hs-0.11.0, We will include all demos in gtk2hs-0.11.1

I think that would be very helpful.  It's a big package with lots of
dependencies, so the first thing I would do is run a couple of demos to
make sure it installed correctly.

As an aside for those interested, the demos are in the gtk2hs tarballs
available for download from the sourceforge page.

Kudos to the team ! Overall it went quite smoothly and will make it
considerably easier to install.  I know that I couldn't get things to
work last time I tried...

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


Re: [Haskell-cafe] Re: Please report any bug of gtk2hs-0.11.0!

2010-07-13 Thread briand
Short version of this post:

Looks like the intsall depends on alex and that dependencies doesn't
appear to be handled, i.e. I had to install alex before proceeding.

why do is it called gtk2hs if you are actually installing package
gtk ;-)

Where's the demo directory ?!

Moral of the story: don't forget to install -dev version of the
necessary libraries. For me that was libpango1.0-dev, libgtk2.0-dev and
libglib2.0-dev.

The long version:

I have a debian system and I expect the problems I found to be
relatively common.  Hope this is useful.

First I found that I needed package alex.

then i was able to 

  cabal install gtk2hs-buildtools

however

  cabal install gtk

didn't work:

Configuring glib-0.11.0...
setup: The pkg-config package glib-2.0 is required but it could not be
found. cabal: Error: some packages failed to install:
gio-0.11.0 depends on glib-0.11.0 which failed to install.
glib-0.11.0 failed during the configure step. The exception was:
ExitFailure 1
gtk-0.11.0 depends on glib-0.11.0 which failed to install.
pango-0.11.0 depends on glib-0.11.0 which failed to install.

  cabal install glib

Configuring glib-0.11.0...
setup: The pkg-config package glib-2.0 is required but it could not be
found. cabal: Error: some packages failed to install:
glib-0.11.0 failed during the configure step. The exception was:
ExitFailure 1

now it's not obvious to me at this point if it's referencing a cabal
package glib-2.0 or the unix libs.  But I'm going to guess it's
actually the unix libs.

I do have the unix libs installed :

ii  libglib2.0-0
2.24.1-1   The GLib library of C routines

However I remembered that annoying little thing that there is always
those darn -dev versions of the lib that you need when you actually
want to compile against libraries. So I installed it and got farther
along, crashing on pango.

Turns out it's the same problem.  So install libpango1.0-dev and
continue...

Stopped again on gtk+, aka gtk libgtk2.0-dev.  Installed it, and
trudged on.

I noticed that the install process stays at this point for a long
time:

Preprocessing library gtk-0.11.0...

But it does eventually continue, and it even completes successfully !

Strangely, at this point, I find that I don't know that I actually have
gtk2hs installed.  I know that this sound kinda dumb, but I just did
cabal install gtk, right ?  I immediately tried cabal install
gtk2hs, which said no such library, and realized that gtk was it :-)

So I'd like to run a demo to make sure things are installed properly.

Running the demos.
--

To get started, you can compile and run one of the programs that reside
in the demo/ directory in the respective packages. For example:

~/gtk2hs/gtk/demo/hello:$ make


But after the installation the demo directory is nowhere to be found.
Do you need to pull it in with darcs ??


 Brian

On Tue, 13 Jul 2010 11:42:26 +0200
Christian Maeder christian.mae...@dfki.de wrote:

 Andy Stewart schrieb:
  Hi all,
  
  We plan to release bug fix version : gtk2hs-0.11.1
  
  Please report any bug of gtk2hs-0.11.0, we will fix it before
  release gtk2hs-0.11.1
 
 I'm looking forward for this bug-fix release (since gtk2hs-0.11.0 did
 not work for me).
 
 Because I've almost missed this message I reply to
 gtk2hs-us...@lists.sourceforge.net, too.
 
 Christian
 
  
  We plan to add many new APIs in gtk2hs-0.12.0, 
  so gtk2hs-0.11.1 will be the last stable version with current APIs.
  
  Thanks for your help!
  
-- Andy
 ___
 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] mixing map and mapM ?

2010-05-06 Thread briand
On Thu, 06 May 2010 12:00:01 +0100
Neil Brown nc...@kent.ac.uk wrote:


 At which point I prefer Ivan's liftM version rather than the above 
 section (or worse: using ($) prefix).  The original request is a 
 relatively common thing to want to do, so I was slightly surprised
 that hoogling for:
 
 (b - c) - (a - f b) - a - f c
 
 didn't turn up any relevant results.  This function is a lot like
 (=) but with a pure rather than side-effecting function on the
 left-hand side.
 

ha ! I had actually remembered to hoogle :-) and didn't get anything
either, only I wasn't sure I put the signature in correctly.

Brian

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


[Haskell-cafe] mixing map and mapM ?

2010-05-05 Thread briand

I was doing the following:


do status - mapM PF.getFileStatus filenames
   let times = map PF.modificationTime status
   let sorted = sortBy (\(_, t1) (_,t2) - compare t1 t2) (zip filenames times)

and I thought, surely I can combine the status and times definitions into one 
line, only I can't.

Hint ?

Thanks,

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


Re: [Haskell-cafe] mixing map and mapM ?

2010-05-05 Thread briand
On Thu, 6 May 2010 15:07:30 +1000
Ivan Miljenovic ivan.miljeno...@gmail.com wrote:

 On 6 May 2010 15:01,  bri...@aracnet.com wrote:
 
  I was doing the following:
 
 
  do status - mapM PF.getFileStatus filenames
    let times = map PF.modificationTime status
    let sorted = sortBy (\(_, t1) (_,t2) - compare t1 t2) (zip
  filenames times)
 
 times - mapM (liftM PF.modificationTime . PF.getFileStatus) filenames
 
 However, I'd be tempted to leave it as is (and hope/assume that fusion
 does its magic).
 

well now it's obvious :-)  I did have liftM in there, but just couldn't
quite figure out how to tie things together.

to be completely clear : liftM takes modificationTime from

 Status - EpochTime 

to

 IO Status - IO EpochTime

so now it can operate on the results of getFileStatus, which 
returns `IO Status`.

mapM gathers the [IO EpochTime] into `IO [EpochTime]` and then - gives
[EpochTime].

It's a little more clear in the verbose form, isn't it ?

Thanks !

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


Re: [Haskell-cafe] Intro to Haskell Crypto Libs

2010-04-01 Thread briand
On Thu, 01 Apr 2010 14:14:42 +0200
Günther Schmidt gue.schm...@web.de wrote:

 Hi all,
 
 I'm just starting with Haskells Crypto Libs. Is there a good intro to 
 the subject?
 I intend to use it for license key generation.
 

Applied Cryptography

 http://www.schneier.com/book-applied.html


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


Re: [Haskell-cafe] why doesn't time allow diff of localtimes ?

2010-03-31 Thread briand
On Wed, 31 Mar 2010 01:32:56 -0400
wagne...@seas.upenn.edu wrote:

 Two values of LocalTime may well be computed with respect to
 different timezones, which makes the operation you ask for dangerous.
 First convert to UTCTime (with localTimeToUTC), then compare.

that makes sense.  unfortunately getting the current timezone to
convert to UTC results in the dreaded IO contamination problem...

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


Re: [Haskell-cafe] Re: why doesn't time allow diff of localtimes ?

2010-03-31 Thread briand
On Thu, 01 Apr 2010 06:20:25 +0200
Maciej Piechotka uzytkown...@gmail.com wrote:

 On Wed, 2010-03-31 at 19:29 -0700, bri...@aracnet.com wrote:
  On Wed, 31 Mar 2010 01:32:56 -0400
  wagne...@seas.upenn.edu wrote:
  
   Two values of LocalTime may well be computed with respect to
   different timezones, which makes the operation you ask for
   dangerous. First convert to UTCTime (with localTimeToUTC), then
   compare.
  
  that makes sense.  unfortunately getting the current timezone to
  convert to UTC results in the dreaded IO contamination problem...
  
  Brian
 
 Hmm. Where do you get the local times from in the first place?
 

read it from a file of course :-)

I think I've got it figured out.  it's not too ugly.

One interesting hole in the system is that buildTime can return a
LocalTime _or_ a UTCTime.  That means the same string used to
generate a time can give you two different times.

It seems as thought it should be restricted to always returning a
UTCTime.  If it's going to return a local time it should require an
extra argument of a timezone, shouldn't it ?

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


[Haskell-cafe] why doesn't time allow diff of localtimes ?

2010-03-30 Thread briand

which is a variation of the question, why can't I compare localtimes ?

or am I missing something in Time (yet again).

Thanks,

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


Re: [Haskell-cafe] Re: Category Theory woes

2010-02-06 Thread briand
On Sun, 07 Feb 2010 01:38:08 +0900
Benjamin L. Russell dekudekup...@yahoo.com wrote:

 On Tue, 02 Feb 2010 09:16:03 -0800, Creighton Hogg wrote:
 
  2010/2/2 Álvaro García Pérez agar...@babel.ls.fi.upm.es
  
  You may try Pierce's Basic Category Theory for Computer
  Scientists or Awodey's Category Theory, whose style is rather
  introductory. Both of them (I think) have a chapter about functors
  where they explain the Hom functor and related topics.
 
  
  I think Awodey's book is pretty fantastic, actually, but I'd avoid
  Pierce. Unlike Types and Programming Languages, I think Basic
  Category Theory... is a bit eccentric in its presentation and
  doesn't help the reader build intuition.
 
 I have written an overview of various category theory books, which
 you may find useful, at the following site:
 
 Learning Haskell through Category Theory, and Adventuring in Category
 Land: Like Flatterland, Only About Categories
 http://dekudekuplex.wordpress.com/2009/01/16/learning-haskell-through-category-theory-and-adventuring-in-category-land-like-flatterland-only-about-categories/
 
 Hope this helps.

It does.

Does anybody have any opinions on Pitt, Category Theory and Computer
Science ?


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