[Haskell-cafe] Re: Matching constructors

2006-02-11 Thread Ben Rudiak-Gould

Mark T.B. Carroll wrote:

Creighton Hogg [EMAIL PROTECTED] writes:

data Patootie = Pa Int | Tootie Int
and I want to pull out the indices of all elements of a list 
that have type constructor Tootie, how would I do that?


x = [Pa 3, Tootie 5, Pa 7, Tootie 9, Pa 11]
y = [ i |Tootie i  - x ]
z = [ i | i@(Tootie _) - x ]


I think this is what the OP wanted:

[ i | (i,Tootie _) - zip [0..] x ]

-- Ben

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


[Haskell-cafe] Digrams

2006-02-11 Thread Dominic Steinitz
I've quickly put this together to measure frequencies of pairs of letters 
(e.g. 1st and 2nd) in words. It works fine on a small test data sets but I 
have a feeling that it will perform poorly as it spends a lot of time 
updating a 26*26 array. Before I throw a dictionary at it, does anyone have 
any suggestions?

Thanks, Dominic.
import System.IO
import Data.Char
import Data.Array
import Data.List

main =
   do h - openFile girls2005.txt ReadMode
  c - hGetContents h
  let freqs1 = g 1 2 (lines c) digramArr
  xs = map putStrLn . 
   map show . 
   reverse . 
   sort . 
   map Cell . 
   assocs $ freqs1
  sequence_ xs
  putStrLn Finished

newtype Cell = Cell ((Char,Char),Int)
   deriving Eq

instance Ord Cell where
   Cell (_,i) = Cell (_,j) = i = j

instance Show Cell where
   show (Cell ((i,j),f)) = i : ',' : j : ',' : show f

letters = ['A'..'Z']
 
digramElems = [((i,j),0) | i - letters, j - letters]

digramArr = array (('A','A'),('Z','Z')) digramElems
 
f n m s a = 
   a // [((i,j),x+1)]
   where i = toUpper (s!!(n-1))
 j = toUpper (s!!(m-1))
 x = a!(i,j)
 
g n m [] a = a
g n m (s:ss) a = g n m ss (f n m s a)

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


Re: [Haskell-cafe] Digrams

2006-02-11 Thread Dominic Steinitz
On Saturday 11 Feb 2006 1:09 pm, Jon Fairbairn wrote:
 On 2006-02-11 at 12:25GMT Dominic Steinitz wrote:
  I've quickly put this together to measure frequencies of pairs of letters
  (e.g. 1st and 2nd) in words. It works fine on a small test data sets but
  I have a feeling that it will perform poorly as it spends a lot of time
  updating a 26*26 array. Before I throw a dictionary at it, does anyone
  have any suggestions?

 I think this is the sort of thing for which accumArray was
 invented.
Jon, Much better. Thanks, Dominic.

import System.IO
import Data.Char
import Data.Array
import Data.List

main =
   do h - openFile girls2005.txt ReadMode
  c - hGetContents h
  let xs = map putStrLn . 
   map show . 
   reverse . 
   sort . 
   map Cell . 
   assocs $ f 1 2 (lines c)
  sequence_ xs
  putStrLn Finished

newtype Cell = Cell ((Char,Char),Int)
   deriving Eq

instance Ord Cell where
   Cell (_,i) = Cell (_,j) = i = j

instance Show Cell where
   show (Cell ((i,j),f)) = i : ',' : j : ',' : show f

hit m n l =
   (toUpper (l!!(m-1)), toUpper (l!!(n-1)))

f m n c =
   accumArray (+) 0 (('A','A'),('Z','Z')) [(hit m n l,1) | l - c]___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-11 Thread Lennart Augustsson

Bulat Ziganshin wrote:

Hello Wolfgang,

Saturday, February 11, 2006, 3:17:12 PM, you wrote:


each and every monadic operation is a function!


WJ What do you mean with monadic operatation?  (=), () and return are, of 
WJ course, functions but an I/O action like getChar is *not* a function.  Also a 
WJ list is not a function but a value of the list monad.



type IO a is really RealWorld - (RealWorld,a)


WJ This representation is just there to help people understand what I/O is but 
WJ actually, IO a is a type which is not implementable in ordinary Haskell and 
WJ therefore cannot be a function.  In addition, RealWorld - (RealWorld,a) as 
WJ an explanation of what IO a is has its limitations.  If we run an I/O action, 
WJ we aren't just interested in the final state but also in intermediate states.


{putStr a} is a function, which receives previous world state and
returns updated world state where a is written to the terminal. it's
an _essential_ part of monadic way to I/O


There is nothing in the Haskell specification that tells you how the
IO type is implemented, so you can't say that putStr takes an old
world state and returns a new one.  I've personally done an
implementation that was totally different, so making assumptions
about how IO is implemented is just wrong.

-- Lennart

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


[Haskell-cafe] Haskell XSLT interpreter?

2006-02-11 Thread S. Alexander Jacobson


Has anyone written a pure haskell xslt interpreter?  If not, how 
difficult would it be to do so?


-Alex-


__
S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell XSLT interpreter?

2006-02-11 Thread Neil Mitchell
Hi,

I don't know of any, but there may well be, I've never looked.

It probably wouldn't be that difficult to do, since XSLT is a
functional language. There is probably lots of code in HaXml you could
reuse (since the syntax for XSLT is XML). The only slightly taxing
thing would be that XSLT is not pure (see the document function), so
you may have to put most of it in the IO Monad.

This would be very handy since Yhc uses XSLT to do some stuff (for
example, http://www-users.cs.york.ac.uk/~ndm/yhc/bytecodes.html) and
currently the choices seem to be MSXSL (which is great for me on
Windows, but sucks a bit for others), or Xalan which is very slow.
Having a Haskell XSLT is something I considered doing before, but
never got round to...

Thanks

Neil

On 11/02/06, S. Alexander Jacobson [EMAIL PROTECTED] wrote:

 Has anyone written a pure haskell xslt interpreter?  If not, how
 difficult would it be to do so?

 -Alex-


 __
 S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com
 ___
 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] Haskell XSLT interpreter?

2006-02-11 Thread Colin Paul Adams
 Neil == Neil Mitchell [EMAIL PROTECTED] writes:

Neil Hi, I don't know of any, but there may well be, I've never
Neil looked.

Neil It probably wouldn't be that difficult to do, since XSLT is
Neil a functional language. There is probably lots of code in
Neil HaXml you could reuse (since the syntax for XSLT is
Neil XML). The only slightly taxing thing would be that XSLT is
Neil not pure (see the document function), so you may have to put
Neil most of it in the IO Monad.

In what way is the document() function not pure?

In XSLT 2.0 at least, it is defined in such a way that it can be
implemented as a pure function.

That is, the static context is defined to include a mapping from URIs
to document nodes, and document() returns those document nodes that
it's argument nodes map to.
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Badly designed Parsec combinators?

2006-02-11 Thread Juan Carlos Arevalo Baeza
  So... I see no reason why someone can't just do it themselves, but... 
I was playing around with Parsec (as included in GHC 6.4.1), and I found 
two functions that are... not quite what I believe they should be.


optional :: GenParser tok st a - GenParser tok st ()
optional p  = do{ p; return ()} | return ()

  Now, this completely loses the result of the optional parser. Better 
would be:


optional :: GenParser tok st a - GenParser tok st (Maybe a)
optional p  = do{ x - p; return (Just x) } | return Nothing

  Same thing with manyTill:

manyTill :: GenParser tok st a - GenParser tok st end - GenParser tok 
st [a]

manyTill p end  = scan
   where
 scan  = do{ end; return [] }
   |
 do{ x - p; xs - scan; return (x:xs) }

  Better:

manyTill :: GenParser tok st a - GenParser tok st end - GenParser tok 
st ([a], end)

manyTill p end  = scan
   where
 scan  = do{ endr - end; return ([], endr) }
   |
 do{ x - p; (xs, endr) - scan; return (x:xs, 
endr) }


  Is there any reason I can't see why they are the way they are?

JCAB

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


[Haskell-cafe] building ghc on win with gcc of cygwin, without cygwin1.dll (-mno-cygwin flag) ?

2006-02-11 Thread Marc Weber
Hi.. I've found the nice documentation about building ghc on
haskell.org/ghc - documentation.
There is one chapter (#1) about C compilers and environments to use:
Either  MSYS or cywin   and
gcc of MinGW because gcc of cygwin will link to cygwin1.dll by default
which may change and therefore can brake your apps.
Googling around I've found that there exists the -mno-cygwin flag which
you can use to not include this lib.. So would it might be possible to
get a ghc build not using cygwin.dll with just cygwin ?
I haven't read anything about that in those docs.

Or does this flag simply include cygwin.dll within your apps (statically
linked) ?

#1 
:http://www.haskell.org/ghc/docs/latest/html/building/platforms.html#ghc-cygwin

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