Re: [Haskell-cafe] Embedding Perl RegEx in Haskell

2011-08-21 Thread Brandon Allbery
By the way, if what you're actually looking for on a high level is a
Haskell-like string matching engine, it might be better to go back to the
original sources.  Look up Kleene's work on string pattern matching; while
regexes derive from it, its more direct descendants are the pattern matching
mechanisms in SNOBOL and Icon.  I've thought for a while that the right way
to do it in Haskell is not parsing a program encoded as a string/regex, but
instead a monadic Kleene machine; but I've never managed to work out a
decent functional implementation (too many irons in the fire, not enough
spoons to even keep track of them much less do something useful with them).

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Embedding Perl RegEx in Haskell

2011-08-21 Thread Brandon Allbery
It just occurred to me that about half the list thinks I just reinvented
parser combinators. Not exactly; the thing that distinguishes regexes in
particular, and the one whose implications I can't quite wrap my brain
around, is that the many combinator is actually

 many' = reverse . many

But is it really that simple, and is an implementation with decent
performance and space characteristics really that simple?  Or does something
have to be designed from scratch around longest match semantics to get
decent behavior?  (There's an analogy to folds here.  Using this in place of
Parsec would have terrible space leaks)

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Existential question

2011-08-21 Thread Tom Schouten

On 08/21/2011 05:33 AM, Felipe Almeida Lessa wrote:

On Sat, Aug 20, 2011 at 6:26 PM, Tom Schoutent...@zwizwa.be  wrote:

data Kl i o = forall s. Kl s (i -s -(s, o))

This is an Arrow.  At first I wondered if there was also an associated
Monad, hence the iso function.

Given

   data Kl i o = forall s. Kl s (i -s -(s, o))

   instance ArrrowApply KI where
 ...

then 'ArrowMonad KI' [1] is a monad isomorphic to

   data KIM o = forall s. KIM s (s -  (s, o))

Is this what you are looking for?


Yes, but I run into the same problem.


data Kl i o = forall s. Kl (i - s - (s, o))

-- OK
instance Category Kl where
  id = Kl $ \ i () - ((), i)
  (.) (Kl u2) (Kl u1) = (Kl u12) where
u12 a (s1, s2) = ((s1',s2'), c) where
  (s1', b) = u1 a s1
  (s2', c) = u2 b s2

-- OK
instance Arrow Kl where
  arr f = Kl $ \i () - ((), f i)
  first (Kl u) = (Kl u') where
u' (i, x) s = (s', (o, x)) where
  (s', o) = u i s

-- Can't make this work.  The problem seems to be the same as before:
-- there's no way to require that the hidden types of both Kl
-- constructors are the same.
instance ArrowApply Kl where
  app = Kl $ \((Kl f), a) - f a


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


Re: [Haskell-cafe] Existential question

2011-08-21 Thread Felipe Almeida Lessa
(Code from this e-mail attached.)

On Sun, Aug 21, 2011 at 7:22 AM, Tom Schouten t...@zwizwa.be wrote:
 Yes, but I run into the same problem.

 data Kl i o = forall s. Kl (i - s - (s, o))

You actually forgot the 's' field of KI in my e-mail.  If you define

  data KI i o = forall s. KI s (i - s - (s, o))
  instance Category KI where ...
  instance Arrow KI where ...

You can make

  instance ArrowApply KI where
  app = KI () $ \(KI s u, b) _ - ((), snd $ u b s)

But this is probably very uninteresting, since the state is just thrown away.

However, if you used

  data KIT i o = forall s. Typeable s = KIT s (i - s - (s, o))
  instance Category KIT where ...
  instance Arrow KIT where ...

You could make

  instance ArrowApply KIT where
  app = KIT (toDyn ()) $
  \(KIT s u, b) dyn - first toDyn $ u b (fromDyn dyn s)

This app operator behaves as KI's app when the argument is not very
well behaving (i.e. changing the state type).  However, when the
argument does behave well, it is given the associated state only once.
 All further iterations work as they should.

Note that since ArrowApply is equivalent to Monad, you may also try
going the other way around.  That is, define

  data KIM o = forall s. KIM s (s - (s, o))

  instance Monad KIM where
  return x = KIM () $ \_ - ((), x)
  KIM sx ux = f = KIM sx u
  where
u sx' = let (tx, i) = ux sx'
in case f i of
 KIM sf uf - let (_, o) = uf sf
  in (tx, o)

I haven't checked, but I think that 'Kleisli KIM' is isomorphic to
'KI', and that 'ArrowMonad KI' is isomorphic to 'KIM'.

You may also define

  data KIMT o = forall s. Typeable s = KIMT s (s - (s, o))

  instance Monad KIMT where
  return x = KIMT () $ \_ - ((), x)
  KIMT sx ux = f = KIMT (sx, toDyn ()) u
  where
u (sx', dyn) = let (tx, i) = ux sx'
   in case f i of
KIMT sf uf -
let (tf,  o) = uf (fromDyn dyn sf)
in ((tx, toDyn tf), o)

And the same conjecture applies between 'Kleisli KIMT' and 'KIT', and
between 'KIMT' and 'ArrowMonad KIT'.

Conclusion: Data.Typeable lets you cheat =).

Cheers,

-- 
Felipe.
{-# LANGUAGE ExistentialQuantification #-}

import Prelude hiding (id, (.))
import Control.Arrow
import Control.Category
import Data.Typeable
import Data.Dynamic

--

data KI i o = forall s. KI s (i - s - (s, o))

instance Category KI where
id = arr id
KI s2 u2 . KI s1 u1 = KI s u
  where
s = (s2, s1)
u = \i1 (s2', s1') - let (t1, i2) = u1 i1 s1'
  (t2, o)  = u2 i2 s2'
  in ((t2, t1), o)

instance Arrow KI where
arr f = KI () $ \i _ - ((), f i)
first (KI s u) = KI s $ \(b, d) s - let (t, c) = u b s
in (t, (c, d))

instance ArrowApply KI where
app = KI () $ \(KI s u, b) _ - ((), snd $ u b s)

type KI_M = ArrowMonad KI

--

data KIT i o = forall s. Typeable s = KIT s (i - s - (s, o))

instance Category KIT where
id = arr id
KIT s2 u2 . KIT s1 u1 = KIT s u
  where
s = (s2, s1)
u = \i1 (s2', s1') - let (t1, i2) = u1 i1 s1'
  (t2, o)  = u2 i2 s2'
  in ((t2, t1), o)

instance Arrow KIT where
arr f = KIT () $ \i _ - ((), f i)
first (KIT s u) = KIT s $ \(b, d) s - let (t, c) = u b s
in (t, (c, d))

instance ArrowApply KIT where
app = KIT (toDyn ()) $
\(KIT s u, b) dyn - first toDyn $ u b (fromDyn dyn s)

type KIT_M = ArrowMonad KIT

--

data KIM o = forall s. KIM s (s - (s, o))

instance Monad KIM where
return x = KIM () $ \_ - ((), x)
KIM sx ux = f = KIM sx u
where
  u sx' = let (tx, i) = ux sx'
  in case f i of
   KIM sf uf - let (_, o) = uf sf
in (tx, o)

type KIM_A = Kleisli KIM

--

data KIMT o = forall s. Typeable s = KIMT s (s - (s, o))

instance Monad KIMT where
return x = KIMT () $ \_ - ((), x)
KIMT sx ux = f = KIMT (sx, toDyn ()) u
where
  u (sx', dyn) = let (tx, i) = ux sx'
 in case f i of
  KIMT sf uf -
  let (tf,  o) = uf (fromDyn dyn sf)
  in ((tx, toDyn tf), o)

type KIMT_A = Kleisli KIMT
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

[Haskell-cafe] why the name lambda calculus?

2011-08-21 Thread C K Kashyap
Hi,
Can someone please tell me what is the root of the name lambda calculus? Is
it just because of the symbol lambda that is used?
Why not alpha or beta calculus?
Regards,
Kashyap
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Failed link to mixed-language shared object

2011-08-21 Thread David Banas

 ghc -dynamic -o ami_test -L. -lami ami_test.o
 ./libami.so: undefined reference to `__stginit_haskell98_MarshalArray_'
 ./libami.so: undefined reference to `__stginit_haskell98_MarshalError_'
 collect2: ld returned 1 exit status

I was able to solve this by changing these lines:

import MarshalArray
import MarshalError

to read:

import Foreign.Marshal.Array
import Foreign.Marshal.Error

I don't understand why this worked, since the available symbols in the 2 
respective libraries appear totally similar:

dbanas@dbanas-eeepc:/usr/lib/ghc-6.12.3$ nm -g 
haskell98-1.0.1.1/libHShaskell98-1.0.1.1.a | grep 'MarshalArray'
MarshalArray__1.o:
0030 T __stginit_haskell98_MarshalArray
 T __stginit_haskell98_MarshalArray_
dbanas@dbanas-eeepc:/usr/lib/ghc-6.12.3$ nm -g -D 
haskell98-1.0.1.1/libHShaskell98-1.0.1.1-ghc6.12.3.so | grep 'MarshalArray'
2b68 T __stginit_haskell98_MarshalArray
2b24 T __stginit_haskell98_MarshalArray_dyn

dbanas@dbanas-eeepc:/usr/lib/ghc-6.12.3$ nm -g base-4.2.0.2/libHSbase-4.2.0.2.a 
| grep '__stginit_.*Foreign.*Marshal.*Array'
006c T __stginit_base_ForeignziMarshalziArray
 T __stginit_base_ForeignziMarshalziArray_
{Some output omitted.}
dbanas@dbanas-eeepc:/usr/lib/ghc-6.12.3$ nm -g -D 
base-4.2.0.2/libHSbase-4.2.0.2-ghc6.12.3.so | grep 
'__stginit_.*Foreign.*Marshal.*Array'
003dc8cc T __stginit_base_ForeignziMarshalziArray
003dc834 T __stginit_base_ForeignziMarshalziArray_dyn

Can anyone shed some light on this?

Thanks!


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


Re: [Haskell-cafe] why the name lambda calculus?

2011-08-21 Thread Jack Henahan
The short answer is because Church said so. But yes, it is basically because 
λ is the abstraction operator in the calculus.

Why not alpha or beta calculus? What would we call alpha and beta conversion, 
then? :D

On Aug 21, 2011, at 12:37 PM, C K Kashyap wrote:

 Hi,
 Can someone please tell me what is the root of the name lambda calculus? Is 
 it just because of the symbol lambda that is used?
 Why not alpha or beta calculus?
 Regards,
 Kashyap
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

Jack Henahan
jhena...@uvm.edu
==
Computer science is no more about computers than astronomy is about telescopes.
-- Edsger Dijkstra
==


398E692F.gpg
Description: application/apple-msg-attachment

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


Re: [Haskell-cafe] why the name lambda calculus?

2011-08-21 Thread Christopher Done
IIRC Church found it easy to write on paper.

On 21 August 2011 21:11, Jack Henahan jhena...@uvm.edu wrote:
 The short answer is because Church said so. But yes, it is basically 
 because λ is the abstraction operator in the calculus.

 Why not alpha or beta calculus? What would we call alpha and beta conversion, 
 then? :D

 On Aug 21, 2011, at 12:37 PM, C K Kashyap wrote:

 Hi,
 Can someone please tell me what is the root of the name lambda calculus? Is 
 it just because of the symbol lambda that is used?
 Why not alpha or beta calculus?
 Regards,
 Kashyap
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

 Jack Henahan
 jhena...@uvm.edu
 ==
 Computer science is no more about computers than astronomy is about 
 telescopes.
 -- Edsger Dijkstra
 ==



 ___
 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] why the name lambda calculus?

2011-08-21 Thread Niklas Larsson
From Cardone, Hindley History of Lambda-calculus and
Combinatory Logic[1]:

(By the way, why did Church choose the notation “λ”? In [Church,
1964, §2] he stated clearly that it came from the notation “ˆ x” used
for class-abstraction by Whitehead and Russell, by first modifying “ˆ
x” to “∧x” to distinguish function-abstraction from class-abstraction,
and then changing “∧” to “λ” for ease of printing. This origin was
also reported in [Rosser, 1984, p.338]. On the other hand, in his
later years Church told two enquirers that the choice was more
accidental: a symbol was needed and “λ” just happened to be chosen.)

[1] http://www-maths.swan.ac.uk/staff/jrh/papers/JRHHislamWeb.pdf

-- Niklas
2011/8/21 Christopher Done chrisd...@googlemail.com:
 IIRC Church found it easy to write on paper.

 On 21 August 2011 21:11, Jack Henahan jhena...@uvm.edu wrote:
 The short answer is because Church said so. But yes, it is basically 
 because λ is the abstraction operator in the calculus.

 Why not alpha or beta calculus? What would we call alpha and beta 
 conversion, then? :D

 On Aug 21, 2011, at 12:37 PM, C K Kashyap wrote:

 Hi,
 Can someone please tell me what is the root of the name lambda calculus? Is 
 it just because of the symbol lambda that is used?
 Why not alpha or beta calculus?
 Regards,
 Kashyap
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

 Jack Henahan
 jhena...@uvm.edu
 ==
 Computer science is no more about computers than astronomy is about 
 telescopes.
 -- Edsger Dijkstra
 ==



 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] custom SQL-to-Haskell type conversion in HDBC

2011-08-21 Thread Richard O'Keefe

On 20/08/2011, at 11:41 PM, Erik Hesselink wrote:
 
 This is the way I was taught to do it in physics. See also 
 http://en.m.wikipedia.org/wiki/Significance_arithmetic

There are at least two different readings of fixed precision arithmetic.

(1) A number with d digits after the decimal point is
a *precise* integer times 10**-d.

Under this reading,   scale(x) ± scale(y) = scale(max(x,y))
  scale(x) × scale(y) = scale(x+y)
  scale(x) ÷ scale(y) = an exact rational number
  scale(x)  scale(y) is well-defined even when x ~= y
  scale(x) = scale(y) is well-defined even when x ~= y

(2) A number with d digits after the decimal point represents
*some* number in the range (as written) ± (10**-d)/2

Under this reading,   scale(x) ± scale(y) = scale(min(x,y))
  scale(x) × scale(y) = depends on the value of the 
numbers
  scale(x)  scale(y) is often undefined even when x = y
  scale(x) = scale)y) is often undefined even when x = y

The web page Erik Hesselink pointed to includes the example 8.02*8.02 = 64.3
(NOT 64.32).

Values in data bases often represent sums of money, for which reading (1) is
appropriate.  One tenth of $2.53 is $0.253; rounding that to $0.25 would in
some circumstances count as fraud.

Of course, values in data bases often represent physical measurements, for which
reading (2) is appropriate.  There is, however, no SQL data type that expresses
this intent.



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


Re: [Haskell-cafe] custom SQL-to-Haskell type conversion in HDBC

2011-08-21 Thread Richard O'Keefe

On 21/08/2011, at 3:01 AM, Henry House wrote:
 No, I want a data type in Haskell that mirrors the data type in the
 RDBMS, not conversion of RDBMS fixed-precision data into something else
 (Rational). If the data in the RDBMS represented a rational number of
 arbitrary precision, then they would have been stored in the RDBMS as a
 rational data type (assuming that the database was designed sensibly, of
 course).

How?  There is no rational data type in standard SQL.
Arbitrary precision really does not fit the classic SQL model of
fixed size columns very well.

 The limitations of the SQL backend are deliberately chosen (no
 one is forced to use fixed-precision numeric data types in PostgreSQL;
 arbitrary-precision numeric is available as well as a true rational with
 a contrib module).

Can you talk to the designer of the data base in question?
Do you know whether they were interested in exploiting features of
PostgreSQL or whether they were interested in portability?
Are you certain that 2.00 will always be reported as 2.00 and
never as 2.0?




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


[Haskell-cafe] Need help Very strange space behavior

2011-08-21 Thread bob zhang
Hi all,
 I thought that Cont Monad is just equivalent to CPS Transformation, so
if I have
a monadic sum, if I run in Identity Monad, it will suck due to
stackoverflow, and if
I run it in Cont Monad, it will okay due to tail recursion. So I write a
simple program
to verify my idea. But to my surprise, the result is unreasonable due to my
limited knowledge.
All programs are compiled ghc --make Test.hs -o test  ./test
  Thank you in advance, the clearer the better!! (I am really confused)
in the comments, suck means stackoverflow.

sum0 n = if n==0  then  0  else n + sum0 (n-1)
sum1 n = if  n==0  then return 0 else sum1 (n-1) = \ v -  seq v (return
(n+v))

sum2 n k = if n == 0 then k 0 else sum2 n (\v - k (n +
v))

sum3 n k = if n == 0 then k 0 else sum3 n (\ !v - k (n +
v))

sum4 n k = if n == 0 then k 0 else sum4 n (\ v - seq v ( k (n +
v)))

sum5 n = if  n==0  then return 0 else sum5 (n-1) = \ v -   (return
(n+v))

-- main = print (sum0 300)
--  suck  reasonable

-- main = print (flip runCont id (sum1 300))
-- rock 180M memory reasonable, but I am not clear why seq needed here,
since its continuation is not applied until n goes to 0

-- main = print (flip runCont id (sum5 300))
-- suck -- why?

-- main = print (flip runCont (const 0) (sum1 300))
-- rock 130M memory   -- reasonable

-- main = print (flip runCont (const 0) (sum5 300))
-- rock 118M memory   -- reasonable

-- main = print (sum2 300 (const 0))
-- a lot of memory (more than 1G)   -- I thought sum2 is equivalent to sum5
(when sum5 is in Cont Monad), why?

-- main = print (sum3 300 (const 0))
-- a lot of memory -- I thought sum3 is equivalent to sum1(Cont Monad), why?


-- main = print (runIdentity  (sum1 300))
-- suck -- exactly what I want

-- main = print (sum3 300 id)
-- a lot of memory -- equivalent to sum1 why?

-- main = print (sum4 300 id) -
- a lot of memory  -- equivalent to sum1 why?

-- main = print (sum [1 .. 300]) -- suck -- src sum = foldl (+)
0
-- reasonable
-- main = print (foldl' (+) 0 [1 .. 300]) -- rock 1.5M
memory
-- reasonable


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


Re: [Haskell-cafe] custom SQL-to-Haskell type conversion in HDBC

2011-08-21 Thread Brandon Allbery
On Sun, Aug 21, 2011 at 20:29, Richard O'Keefe o...@cs.otago.ac.nz wrote:

 Values in data bases often represent sums of money, for which reading (1)
 is
 appropriate.  One tenth of $2.53 is $0.253; rounding that to $0.25 would in
 some circumstances count as fraud.

 Of course, values in data bases often represent physical measurements, for
 which
 reading (2) is appropriate.  There is, however, no SQL data type that
 expresses
 this intent.


Interestingly, my original exposure to this was math for physics, which
would imply reading (2) if I understand this correctly, yet I was taught
(1).  (Later exposure was for business databases, so (1) was still
appropriate.)

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe