[Haskell-cafe] Problem installing svgcairo

2011-10-23 Thread Roly Perera
Hi,

I'm having a problem installing svgcairo with Cabal, which I need for
something else.

I don't know what's going on, but something (maybe a C preprocessor,
judging by Google search results) barfs with the complaint:

./Graphics/Rendering/Cairo/SVG.chs:209:28: error: missing binary
operator before token (

I can't find the file SVG.chs on my system to inspect this line, but
perhaps I'm looking in the wrong place.

Has anyone encountered this? Am I perhaps using the wrong version of
Cairo or Gtk? Any suggestions welcome.

thanks
Roly


==
$ cabal install svgcairo

Resolving dependencies...
[1 of 2] Compiling SetupWrapper (
/tmp/svgcairo-0.12.125554/svgcairo-0.12.1/SetupWrapper.hs,
/tmp/svgcairo-0.12.125554/svgcairo-0.12.1/dist/setup/SetupWrapper.o )
[2 of 2] Compiling Main (
/tmp/svgcairo-0.12.125554/svgcairo-0.12.1/Setup.hs,
/tmp/svgcairo-0.12.125554/svgcairo-0.12.1/dist/setup/Main.o )
Linking /tmp/svgcairo-0.12.125554/svgcairo-0.12.1/dist/setup/setup ...
[1 of 2] Compiling Gtk2HsSetup  ( Gtk2HsSetup.hs,
dist/setup-wrapper/Gtk2HsSetup.o )
[2 of 2] Compiling Main ( SetupMain.hs, dist/setup-wrapper/Main.o )
Linking dist/setup-wrapper/setup ...
Configuring svgcairo-0.12.1...
Preprocessing library svgcairo-0.12.1...
./Graphics/Rendering/Cairo/SVG.chs:209:28: error: missing binary
operator before token (
gtk2hsC2hs: Error during preprocessing chs file
cabal: Error: some packages failed to install:
svgcairo-0.12.1 failed during the building phase. The exception was:
ExitFailure 1

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


[Haskell-cafe] Text.Parsec.Prim

2011-08-29 Thread Roly Perera
Hi,

I seem to have some trouble accessing this module. I would like to use
the type synonym ParsecT directly.

I'm running GHC 6.12.1. According to Hoogle, the type I want is part
of parsec-3.1.1, in module Text.Parsec.Prim. But if try to import
Text.Parsec.Prim, GHC complains

Could not find module `Text.Parsec.Prim':

Can anyone help me with this? In the 2+ years I've been using parsec
I've never managed to use ParsecT directly, but now it would be very
useful.

thanks,
Roly

In verbose mode, GHC reports:

Glasgow Haskell Compiler, Version 6.12.1, for Haskell 98, stage 2
booted by GHC version 6.12.1
Using binary package database: /usr/lib/ghc-6.12.1/package.conf.d/package.cache
Using binary package database:
/home/rolyp/.ghc/x86_64-linux-6.12.1/package.conf.d/package.cache
hiding package Cabal-1.8.0.2 to avoid conflict with later version Cabal-1.10.2.0
hiding package QuickCheck-1.2.0.0 to avoid conflict with later version
QuickCheck-2.1.0.2
hiding package base-3.0.3.2 to avoid conflict with later version base-4.2.0.0
wired-in package ghc-prim mapped to
ghc-prim-0.2.0.0-9d35c97e886f807a1e6d024aaa91dcec
wired-in package integer-gmp mapped to
integer-gmp-0.2.0.0-9a51ffb34a83618a1a3d4e472b9977a0
wired-in package base mapped to base-4.2.0.0-2cc27b7e43511c4ca001642a7f77a8f6
wired-in package rts mapped to builtin_rts
wired-in package haskell98 mapped to
haskell98-1.0.1.1-0fdaf3b26bc38c43ce8371edf538dbf6
wired-in package template-haskell mapped to
template-haskell-2.4.0.0-bbc7c61990d2fe9d20be2deb924f833c
wired-in package dph-seq mapped to
dph-seq-0.4.0-52cfd6db5fc09a2abf793cd6a856a392
wired-in package dph-par mapped to
dph-par-0.4.0-b4f339fed900d7bc4b3db61526caf863
Hsc static flags: -static

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


Re: [Haskell-cafe] Text.Parsec.Prim

2011-08-29 Thread Roly Perera
Cool. I assumed that since I already had Parsec installed as part of
the Haskell Platform it wouldn't have made any difference, but
actually it sorted it. Thanks a lot!

On 29 August 2011 18:25, Antoine Latter aslat...@gmail.com wrote:
 There might be something off about your packages database.

 I just did:

 $ cabal update
 $ cabal install parsec
 $ ghci
 import Text.Parsec.Prim

 and it went fine.

 Also, the module Text.Parsec re-exports the entirety of
 Text.Parsec.Prim, so you won't get much advantage importing the
 Prim module on its own.

 Antoine

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


[Haskell-cafe] String rewriting

2010-05-20 Thread Roly Perera
Hi,

I'm looking for a simple way to rewrite strings according to simple
composable rules like:

replace _ by \\(\\hole\\)
replace -n where n matches an integer by ^{n}

so that I can import some pretty-printed output into a LaTeX alltt
environment. I'm guessing that this nice functional stream
transformation problem has been solved thousands of times. Could
anyone point me to a simple package that would do this for me?

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


[Haskell-cafe] Location of library documentation with 6.12.1?

2010-05-01 Thread Roly Perera
Hi,

I've just upgraded from 6.10.1 to 6.12.1 and can't seem to find all
the library documentation. This page is apparently the documentation
root:

http://www.haskell.org/ghc/docs/6.12.1/html/

but if I click through to the Haskell Hierarchical Libraries page

http://www.haskell.org/ghc/docs/6.12.1/html/libraries/index.html

I can't for example find Control.Monad.State. I guess I'm missing
something obvious about how things are organised?

thanks in advance,
Roly
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Location of library documentation with 6.12.1?

2010-05-01 Thread Roly Perera
Thanks for those replies, it's a lot clearer now. By the way, is there
a unified package view for all the documentation shipped with the
Haskell Platform, or do I need to know what library to look in?

cheers,
Roly

On 1 May 2010 15:33, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:
 Roly Perera roly.per...@dynamicaspects.org writes:
 I've just upgraded from 6.10.1 to 6.12.1 and can't seem to find all
 the library documentation. This page is apparently the documentation
 root:

 http://www.haskell.org/ghc/docs/6.12.1/html/

 but if I click through to the Haskell Hierarchical Libraries page

 http://www.haskell.org/ghc/docs/6.12.1/html/libraries/index.html

 I can't for example find Control.Monad.State. I guess I'm missing
 something obvious about how things are organised?

 This is part of the mtl library.  Prior to GHC 6.10.4, this used to be
 part of the extralibs that were often bundled with GHC and thus were
 on GHC's documentation page.  With 6.10.4, extralibs was replaced with
 the Haskell Platform and as such is no longer featured on GHC's
 documentation page.

 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com

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


[Haskell-cafe] Using Parsec with other monads

2008-11-28 Thread Roly Perera
Hi,

I've spent some time writing a parser using the Parsec library and was looking 
forward to being able to plug in some side-behaviour once I'd got the parser 
working.

Now it seems I can't actually do that in a nice way because Parsec appears to 
be fixed to a simple State monad.

I found this mentioned in the Cafe archives, but not much discussion.  Is there 
a reason Parsec wasn't implemented using the monad transformer approach?  Are 
there any plans to open it up?  It's a nice powerful library and a natural 
thing to want to do for example would be to plug in something like a Reader to 
track a variable context.  I guess one could abuse the State monad to achieve 
the goal but that feels like the wrong tool for the job.

Any insights appreciated.

thanks,
Roly



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


[Haskell-cafe] Re: Type classes question

2008-10-08 Thread Roly Perera
Ryan Ingram ryani.spam at gmail.com writes:

 [...]
 
 Here's another possible solution:
 
  newtype AsFunctor s a = AF { fstream :: (s a) }
  instance (Stream f) = Functor (AsFunctor f) where
  fmap f (AF s) = AF (fmapStreamDefault f s)
 
 Now to use fmap you wrap in AF and unwrap with fstream.
 
 None of the existing solutions are really satisfactory, unfortunately.

Bulat Ziganshin bulat.ziganshin at gmail.com writes:

 http://haskell.org/haskellwiki/OOP_vs_type_classes may be useful
 
Many thanks to you both for the clarification and pointers.

cheers,
Roly



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


[Haskell-cafe] Type classes question

2008-10-07 Thread Roly Perera
Hi,

I'm reasonably well versed in Haskell but fairly new to defining type classes.  
In particular I don't really understand how to arrange for all instances of X 
to also be instances of Y.  

It's quite possibly that my question is ill-posed, so I'll make it as concrete 
as possible: in the following code, I define a Stream class, with two 
instances, Stream1 and Stream2.  How do I arrange for there to be one 
implementation of Functor's fmap for all Stream instances?  I currently rely on 
delegation, but in the general case this isn't nice.

I guess I'm either misunderstanding what it is I'm trying to achieve, or how to 
do this kind of thing in Haskell.  Any help would be greatly appreciated.

many thanks,
Roly Perera



{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, 
ExistentialQuantification, FunctionalDependencies #-}

module Test where

---
-- Just some helpers.
---

-- Product map.
prod :: (a - b) - (c - d) - (a, c) - (b, d)
f `prod` g = \(a, c) - (f a, g c)

-- Diagonal.
diag :: a - (a, a)
diag x = (x, x)

-- Mediating morphism into the product.
both :: (a - b) - (a - c) - a - (b, c)
both f g = prod f g . diag

---
-- Abstract stream.
---
class Stream s a | s - a where
first :: s - a
next :: s - s
fby :: a - s - s

-- I want every Stream to be a Functor.
fmap_ :: Stream s' b = (a - b) - s - s'
fmap_ f = uncurry fby . both (f . first) (fmap_ f . next)

---
-- Implementation 1.
---
data Stream1 a = a : Stream1 a

instance Functor Stream1 where
fmap = fmap_

instance Stream (Stream1 a) a where
first (x : _) = x
next (_ : xs) = xs
fby = (:)

---
-- Implementation 2.
---
data Stream2 a = forall b . S b (b - a) (b - b)

instance Functor Stream2 where
fmap = fmap_

instance Stream (Stream2 a) a where
first (S x c _) = c x
next (S x c i) = S (i x) c i
fby y s = S (y, s) fst (uncurry (,) . both first next . snd)




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


[Haskell-cafe] Kleisli composition operator

2008-08-03 Thread Roly Perera
Hi,

I'm obviously missing something basic here but I don't seem to be able to use
the = operator which is apparently defined in the Prelude and also in
Control.Monad.

My imports are:

import Prelude hiding (abs, lookup, init)

import Data.Maybe
import Data.List as List hiding (lookup, insert, delete, union, init)
import Data.Map as Map hiding (update, delete, union, null, findIndex)
import qualified Data.Tree as Tree
import Control.Monad
import Control.Monad.State

Any suggestions anyone?

thanks,
Roly Perera


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


[Haskell-cafe] Re: Kleisli composition operator

2008-08-03 Thread Roly Perera
 I'm obviously missing something basic here but I don't seem to be able to use
 the = operator which is apparently defined in the Prelude and also in
 Control.Monad.

Sorry, I wasn't very clear in my original posting.  What I meant to say is that
the compiler seems to be unable to find a definition of =.  I get the message:

Not in scope: `='

My understanding is that I shouldn't need to import this at all by default, and
that importing Control.Monad should also pick it up.
 
 My imports are:

 import Prelude hiding (abs, lookup, init)
 
 import Data.Maybe
 import Data.List as List hiding (lookup, insert, delete, union, init)
 import Data.Map as Map hiding (update, delete, union, null, findIndex)
 import qualified Data.Tree as Tree
 import Control.Monad
 import Control.Monad.State
 
 Any suggestions anyone?
 
 thanks,
 Roly Perera


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


[Haskell-cafe] Re: Kleisli composition operator

2008-08-03 Thread Roly Perera
Daniel Fischer daniel.is.fischer at web.de writes:

 Which implementation are you using?
 IIRC, GHC didn't have it in Control.Monad before the 6.8 branch.

Duncan Coutts [EMAIL PROTECTED] writes:

 It's not in the Prelude but it is in Control.Monad in base version 3
 and later. You're probably using an older GHC which has base version
 2.x.

Thanks for the quick responses.  Looks like I need to install a version later
than 6.8.

Roly


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