[Haskell-cafe] Compiling hugs - stop on missing symbol

2005-11-03 Thread Dusan Kolar

Hello all,

 I don't know if this is the right place to ask about
how to compile hugs, but I'll try. :-)

My machine identifies this way:
Linux mymachine 2.6.14 #1 SMP Mon Oct 31 10:55:16 CET 2005 i686 athlon 
i386 GNU/Linux


I've downloaded this SRC package of hugs:
hugs98-Mar2005-patched.tar.gz

Download, unpack - OK

./configure --prefix=/mnt/data/FLP --enable-timer
does not complain, suggests to perform make; make install

Unfortunately, make stops with this error:

gcc  runhugs.o server.o builtin.o char.o compiler.o errors.o evaluator.o 
ffi.o goal.o input.o machdep.o machine.o module.o opts.o output.o 
plugin.o script.o static.o storage.o strutil.o subst.o type.o version.o  
-lreadline -lncurses -lm -ldl  -o runhugs

evaluator.o(.text+0x137): In function `evaluator':
/mnt/data/FLP/Downloads/hugs98-Mar2005-patched/src/evaluator.c:98: 
undefined reference to `updateTimers'

collect2: ld returned 1 exit status
make: *** [runhugs] Error 1

Well, yes, the symbol is definitely missing, as timer.c, which defines 
the symbol,
is included in hugs.c, which is not in the list of linked files. 
Nevertheless,
I don't think including the file manually would help. Moreover, probably 
configure

has produced a wrong Makefile.

Any suggestions how to make it work?

Dusan



--

Dusan Kolartel: +420 54 114 1238
UIFS FIT VUT Brno  fax: +420 54 114 1270
Bozetechova 2   e-mail: [EMAIL PROTECTED]
Brno 612 66
Czech Republic

--

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


Re: [Haskell-cafe] Vector/matrix arithmetic

2005-11-03 Thread Henning Thielemann

On Wed, 2 Nov 2005, James McNeill wrote:

 On http://haskell.org/hawiki/FunDeps another approach is sketched out that
 looks far more appealing to me. This is to create Vector and Matrix types
 that can use overloaded arithmetic operators. It uses functional
 dependencies, and the resulting syntax looks a lot like what you can do
 using C++ or Matlab.

Recently there was a long discussion about the design of a linear algebra
library.  As an answer to your mail I setup an overview of such
discussions and related software packages.
 http://haskell.org/hawiki/LinearAlgebra

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


[Haskell-cafe] Compiled hugs - on overload crashes

2005-11-03 Thread Dusan Kolar

Hello again,

 without the --endable-timer option, I have managed to compile hugs. 
Nevertheless,

I was not successfull with doc. OK, I don't care about it, but anyway...

 I've run serveral tests. One of them is appended - for trial just type 
cesty (1,1) -
it's a kind of state-space search implementation (horse problem) made by 
a student long

time ago, without any optimization, for testing very good.

 My older hugs interpreter stops with error: ERROR - Control stack overflow
GHCi stops with the same error: *** Exception: stack overflow
That's OK, really, that's correct behavior after printing some results.

 Nevertheless, the new hugs compilation stops with this: Segmentation 
Fault(coredump)
And that's probably not the correct end. May I do something wrong? I've 
thought
that configure + make + make install_all_but_docs (no doc compiled) 
should work.


 Sorry for bothering if this is trivial or off topic.


 Regards, hoping for help,

   Dusan

--

Dusan Kolartel: +420 54 114 1238
UIFS FIT VUT Brno  fax: +420 54 114 1270
Bozetechova 2   e-mail: [EMAIL PROTECTED]
Brno 612 66
Czech Republic

--

-
-- Bohuslav Krena (xkrena00)2 IVT 23
-- FLP - Funkcionalni a logicke programovani
-- Project 1 - Kun na sachovnici
--
-- Zadani:
-- ---
-- Ze zadaneho pole najdete cestu tak, abyste prosli vsechna pole,
-- ale na zadne pole nesmite vstoupit dvakrat.
--
-

type Pole = (Int,Int)
type Cesta = [Pole]

-- Test: z pole (1,1) - Pentium II Celeron 300 MHz.
--1,2,3,4 ...  1s
--5 ...   2 s
--6 ...  15 s
--7 ... 240 s
--30 ... do 30 minut neskoncil.
--50, 60, 61 ... control stack overflow po nekolika vysledcich.
--62, 65 ... control stack overflow ihned.
--
-- Vrati seznam vyhovujicich cest.
cesty :: Pole - [Cesta]
cesty (s,r) 
   | pridej (s,r) [] == [] 
   = error cesty: Zadane vychozi pole neni na sachovnici.
   | otherwise = hledej [[(s,r)]]

-- Test: jako cesty.
-- Hleda mozne cesty.
hledej :: [Cesta] - [Cesta]
hledej [] = []
hledej (xs:xss)
   | poli xs == 25 = xs : hledej xss
   | otherwise = hledej ( tahni xs (hledej xss) )

-- Test: OK.
-- Vygeneruje tahy na pole, ktera nejsou v dosavadni ceste.
tahni :: Cesta - [Cesta] - [Cesta]
tahni [] ass = ass
tahni (x:xs) ass = spoj (x:xs) (tah x) ass

-- Test: OK.
-- Propoji seznam moznych tahu s puvodni cestou.
spoj :: Cesta - Cesta - [Cesta] - [Cesta]
spoj _ [] ass  = ass
spoj xs (y:ys) ass
   | unikat xs y == [] = spoj xs ys ass
   | otherwise = (unikat xs y) : (spoj xs ys ass)

-- Test: OK.
-- Pokud pole neni v ceste, pak ho pridame.
unikat :: Cesta - Pole - Cesta
unikat xs y
   | clenem xs y == 1 = []
   | otherwise= y:xs

-- Test: OK.
-- Vrati 1, pokud je jiz pole v ceste, jinak vrati 0.
clenem :: Cesta - Pole - Int
clenem [] _ = 0
clenem (x:xs) y
   | x==y = 1
   | otherwise = clenem xs y

-- Test: Lze tahnout i z pole mimo sachovnici.
-- Vytvori seznam poli, na kteje je mozne tahnout.
tah :: Pole - [Pole]
tah (s,r) =  pridej (s+2,r+1)
(pridej (s+2,r-1)
(pridej (s+1,r+2)
(pridej (s+1,r-2)
(pridej (s-1,r+2)
(pridej (s-1,r-2)
(pridej (s-2,r+1)
(pridej (s-2,r-1) [])))

-- Test: OK.
-- Pokud je (s,r) pole sachovnice, tak je prida do seznamu xs.
pridej :: Pole - [Pole] - [Pole]
pridej (s,r) xs
 = if ((s0)  (s6)  (r0)  (r6))
   then (s,r):xs
   else xs

-- Test: OK.
-- Zjisti pocet poli v ceste.
poli :: Cesta - Int
poli [] = 0
poli (x:xs) = 1 + poli xs

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


[Haskell-cafe] Compiled hugs - on overload crashes

2005-11-03 Thread Dusan Kolar

Hello again,

 without the --enable-timer option, I have managed to compile hugs. 
Nevertheless,

I was not successful with doc. OK, I don't care about it, but anyway...

 I've run several tests. One of them is appended - for trial just type: 
cesty (1,1)
/(It's a kind of state-space search implementation (horse problem) made 
by a student long

time ago, without any optimization, for testing very good.)/

 My older hugs interpreter stops with error: ERROR - Control stack overflow
GHCi stops with the same error: *** Exception: stack overflow
That's OK, really, that's correct behavior after printing some results.

 Nevertheless, the new hugs compilation stops with this: Segmentation 
Fault(coredump)
And that's probably not the correct end. May I do something wrong? I've 
thought
that configure + make + make install_all_but_docs (no doc compiled) 
should work.


 Sorry for bothering if this is trivial or off topic.


 Regards, hoping for help,

   Dusan

--

Dusan Kolartel: +420 54 114 1238
UIFS FIT VUT Brno  fax: +420 54 114 1270
Bozetechova 2   e-mail: [EMAIL PROTECTED]
Brno 612 66
Czech Republic

--

-
-- Bohuslav Krena (xkrena00)2 IVT 23
-- FLP - Funkcionalni a logicke programovani
-- Project 1 - Kun na sachovnici
--
-- Zadani:
-- ---
-- Ze zadaneho pole najdete cestu tak, abyste prosli vsechna pole,
-- ale na zadne pole nesmite vstoupit dvakrat.
--
-

type Pole = (Int,Int)
type Cesta = [Pole]

-- Test: z pole (1,1) - Pentium II Celeron 300 MHz.
--1,2,3,4 ...  1s
--5 ...   2 s
--6 ...  15 s
--7 ... 240 s
--30 ... do 30 minut neskoncil.
--50, 60, 61 ... control stack overflow po nekolika vysledcich.
--62, 65 ... control stack overflow ihned.
--
-- Vrati seznam vyhovujicich cest.
cesty :: Pole - [Cesta]
cesty (s,r) 
   | pridej (s,r) [] == [] 
   = error cesty: Zadane vychozi pole neni na sachovnici.
   | otherwise = hledej [[(s,r)]]

-- Test: jako cesty.
-- Hleda mozne cesty.
hledej :: [Cesta] - [Cesta]
hledej [] = []
hledej (xs:xss)
   | poli xs == 25 = xs : hledej xss
   | otherwise = hledej ( tahni xs (hledej xss) )

-- Test: OK.
-- Vygeneruje tahy na pole, ktera nejsou v dosavadni ceste.
tahni :: Cesta - [Cesta] - [Cesta]
tahni [] ass = ass
tahni (x:xs) ass = spoj (x:xs) (tah x) ass

-- Test: OK.
-- Propoji seznam moznych tahu s puvodni cestou.
spoj :: Cesta - Cesta - [Cesta] - [Cesta]
spoj _ [] ass  = ass
spoj xs (y:ys) ass
   | unikat xs y == [] = spoj xs ys ass
   | otherwise = (unikat xs y) : (spoj xs ys ass)

-- Test: OK.
-- Pokud pole neni v ceste, pak ho pridame.
unikat :: Cesta - Pole - Cesta
unikat xs y
   | clenem xs y == 1 = []
   | otherwise= y:xs

-- Test: OK.
-- Vrati 1, pokud je jiz pole v ceste, jinak vrati 0.
clenem :: Cesta - Pole - Int
clenem [] _ = 0
clenem (x:xs) y
   | x==y = 1
   | otherwise = clenem xs y

-- Test: Lze tahnout i z pole mimo sachovnici.
-- Vytvori seznam poli, na kteje je mozne tahnout.
tah :: Pole - [Pole]
tah (s,r) =  pridej (s+2,r+1)
(pridej (s+2,r-1)
(pridej (s+1,r+2)
(pridej (s+1,r-2)
(pridej (s-1,r+2)
(pridej (s-1,r-2)
(pridej (s-2,r+1)
(pridej (s-2,r-1) [])))

-- Test: OK.
-- Pokud je (s,r) pole sachovnice, tak je prida do seznamu xs.
pridej :: Pole - [Pole] - [Pole]
pridej (s,r) xs
 = if ((s0)  (s6)  (r0)  (r6))
   then (s,r):xs
   else xs

-- Test: OK.
-- Zjisti pocet poli v ceste.
poli :: Cesta - Int
poli [] = 0
poli (x:xs) = 1 + poli xs

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


[Haskell-cafe] Socket finalizers

2005-11-03 Thread Joel Reymont

Folks,

I remember a message about this recently and tried googling for it  
but came up empty.


I'm running a bunch of poker bots from ghci and although I'm  
calling hClose on the socket handle, it does not seem to actually  
close when my bots finish. I need to exit ghci for the sockets to close.


How can I tackle this problem? It's important for me that the sockets  
close when I call hClose .


Thanks, Joel

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Threads talking back to parent

2005-11-03 Thread Joel Reymont

So when should I use a STM TChan instead of a regular Chan?

On Oct 31, 2005, at 10:08 PM, ChrisK wrote:


Or perhaps a TChan, if that is more appropriate:

http://www.haskell.org/ghc/docs/latest/html/libraries/stm/Control- 
Concurrent-STM-TChan.html


I like the curried command idiom:


I'm not sure I understand this. Are you trying to show that the same  
logToParent approach can be used with Chan, TChan and MVar below?



do chan - newChan
   let logToParent =  writeChan chan

do tChan - newTChan
   let logToParentSTM = writeTChan tChan
   let logToParent = atomically.logToParentSTM

do mVar - newEmptyMVar
   let logToParent = putMVar mVar


Thanks, Joel

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Socket finalizers

2005-11-03 Thread Tomasz Zielonka
On Thu, Nov 03, 2005 at 05:45:10PM +, Joel Reymont wrote:
 I'm running a bunch of poker bots from ghci and although I'm  
 calling hClose on the socket handle, it does not seem to actually  
 close when my bots finish. I need to exit ghci for the sockets to close.

If these are listening sockets, make sure you did 'setSocketOption
socket ReuseAddr 1'.

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


[Haskell-cafe] Maximum number of sockets

2005-11-03 Thread Joel Reymont
Is there a limit on the maximum number of sockets that's possible to  
open in GHC?


I'm concerned with Mac OSX and Windows.

Thanks, Joel

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Threads talking back to parent

2005-11-03 Thread ChrisK

Joel Reymont wrote:
 So when should I use a STM TChan instead of a regular Chan?
 
 On Oct 31, 2005, at 10:08 PM, ChrisK wrote:
 
 Or perhaps a TChan, if that is more appropriate:

 http://www.haskell.org/ghc/docs/latest/html/libraries/stm/Control-
 Concurrent-STM-TChan.html

 I like the curried command idiom:
 
 
 I'm not sure I understand this. Are you trying to show that the same 
 logToParent approach can be used with Chan, TChan and MVar below?
 
 do chan - newChan
let logToParent =  writeChan chan

 do tChan - newTChan
let logToParentSTM = writeTChan tChan
let logToParent = atomically.logToParentSTM

 do mVar - newEmptyMVar
let logToParent = putMVar mVar
 
 
 Thanks, Joel

Yes, exactly.  I listed several alternatives.

The logToParent approach hides the actualy mechanism in use.  This has 2
advantages:

* You can switch the code for logToParent without messing with the child
code (or type signatures!) The Chan/TChan are non-blocking while the
MVar (or TMVar) would block, so this is a non-trivial difference.

* The child has no reference to the data structure so the only thing it
can do is write/put via logToParent.  If you had passed the chan/var to
the child then it could accidentally start reading from it.  Which would
be bad.

All this is an example of the Haskell is the best imperative language
saying.  An OO language might need a whole class/inferance structure to
support what writeChan chan accomplished by currying.

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


[Haskell-cafe] handling rank 2 types

2005-11-03 Thread Andrew Pimlott
I am trying to use a rank 2 type to enforce a condition on a data
structure.  For the purpose of this message, I am trying to ensure that
a list is empty (ignoring the possibility of bottom elements):

 {-# OPTIONS -fglasgow-exts #-}
 import Control.Monad
 newtype Empty = Empty (forall a. [a])

I want a function

 listToEmpty :: [v] - IO Empty
 listToEmpty l = liftM Empty (mapM no l) where
   no :: a - IO a'
   no x = fail element found

But this gives a less polymorphic error.  I think the problem is that
ghc will not instantiate the a' in IO a' as a higher-rank type
because it occurs within a type contructor.  I believe this is the
restriction referred to at the end of 7.4.9[1].  If I instead write

 uncheckedListToEmpty :: [v] - Empty
 uncheckedListToEmpty l = Empty (map no l) where
   no :: a - a'
   no x = error element found

it compiles, because v' can be instantiated as forall v. Rule v, and
even pass through map with the higher-rank type.

Is there any way to make ghc accept the first definition?  I found this
workaround:

 newtype Any = Any { unAny :: forall a. a }
 listToEmptyAny :: [v] - IO Empty
 listToEmptyAny l = liftM (\l - Empty (map unAny l)) (mapM no l) where
   no :: a - IO Any
   no x = fail element found

But needing a newtype wrapper Empty was bad enough; do I really need one
for every intermediate result (that is inside another type constructor)
as well?  I could probably define a generic family of wrappers

 newtype Forall = Forall (forall a. a)
 newtype Forall1 c1 = Forall1 (forall a. c1 a)
 newtype Forall2 c1 c2 = Forall2 (forall a. c1 c2 a)
...

But I would still have to use them everywhere.  Any other tricks?

Andrew

[1] 
http://haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#universal-quantification

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


[Haskell-cafe] newbie help

2005-11-03 Thread Abhijit Ray
Hi I just started on haskell , i am using the yet another haskell
tutorial by Hal Daume

I wrote the following program and it dint compile.
what's wrong with it

module Main
where

import IO

main = do
hSetBuffering stdin LineBuffering
let testList = makeList
let sum = foldr (+) 0 testList
putStrLn Sum is  ++ show(sum)

makeList = do
putStrLn enter a num
num - getLine
let nbr = read num
if nbr == 0
then do
return []
else do
all -  makeList
return  (nbr : all)
--
the error i get is

Chasing modules from: Sum.hs
Compiling Main ( Sum.hs, Sum.o )

Sum.hs:6:
Couldn't match `[a]' against `IO ()'
Expected type: [a]
Inferred type: IO ()
In the application `putStrLn Sum is '
In the first argument of `(++)', namely `putStrLn Sum is '

Sum.hs:9:
Couldn't match `[b]' against `IO [a]'
Expected type: [b]
Inferred type: IO [a]
In the third argument of `foldr', namely `testList'
In the definition of `sum': sum = foldr (+) 0 testList
-

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


Re: [Haskell-cafe] newbie help

2005-11-03 Thread Tomasz Zielonka
On 11/4/05, Abhijit Ray [EMAIL PROTECTED] wrote:
 I wrote the following program and it dint compile.
 what's wrong with it

 module Main
 where

 import IO

 main = do
 hSetBuffering stdin LineBuffering
 let testList = makeList
 let sum = foldr (+) 0 testList
 putStrLn Sum is  ++ show(sum)

Write either

  testList - makeList

or

  sum - liftM (foldr (+) 0) testList

You probably want the former form.

BTW, there is a sum function in Haskell prelude.

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


Re: [Haskell-cafe] newbie help

2005-11-03 Thread Cale Gibbard
On 04/11/05, Abhijit Ray [EMAIL PROTECTED] wrote:
 Hi I just started on haskell , i am using the yet another haskell
 tutorial by Hal Daume

 I wrote the following program and it dint compile.
 what's wrong with it

 module Main
 where

 import IO

 main = do
 hSetBuffering stdin LineBuffering
 let testList = makeList
 let sum = foldr (+) 0 testList
 putStrLn Sum is  ++ show(sum)

 makeList = do
 putStrLn enter a num
 num - getLine
 let nbr = read num
 if nbr == 0
 then do
 return []
 else do
 all -  makeList
 return  (nbr : all)
 --
 the error i get is

 Chasing modules from: Sum.hs
 Compiling Main ( Sum.hs, Sum.o )

 Sum.hs:6:
 Couldn't match `[a]' against `IO ()'
 Expected type: [a]
 Inferred type: IO ()
 In the application `putStrLn Sum is '
 In the first argument of `(++)', namely `putStrLn Sum is '

 Sum.hs:9:
 Couldn't match `[b]' against `IO [a]'
 Expected type: [b]
 Inferred type: IO [a]
 In the third argument of `foldr', namely `testList'
 In the definition of `sum': sum = foldr (+) 0 testList
 -

 Thanks,
 Abhijit Ray

Hello,

The first error is related to the way in which the following line parses:
 putStrLn Sum is  ++ show(sum)
which is like:
(putStrLn Sum is) ++ (show sum)
It's complaining that you're passing an IO action to (++). It's an
easy fix, add some parens, or a well-placed ($):
putStrLn $ Sum is ++ show sum

The second problem arises due to not running the IO action you wanted to:
 main = do
 hSetBuffering stdin LineBuffering
 let testList = makeList
 let sum = foldr (+) 0 testList
 putStrLn $ Sum is  ++ show sum
What is the type of testList? Well, it must be the same as makeList --
what is makeList's type? The definition of makeList is in the form of
a do-block which carries out an IO computation producing a list of
numbers, so it's (Num a) = IO [a]. Note that this is not a list, so
it's unsuitable for passing to foldr.

What do we do? We run the IO action using -:
 main = do
 hSetBuffering stdin LineBuffering
 testList - makeList
 let sum = foldr (+) 0 testList
 putStrLn $ Sum is  ++ show sum
This will cause the running of main to  *run* the IO action makeList,
getting the result into the list testList, which now has type (Num a)
= [a] (here a is going to be defaulted to Integer, since nothing says
otherwise, and one needs to pick something to be able to read).

Hope this helps, and good luck with Haskell :)
 - Cale
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] handling rank 2 types

2005-11-03 Thread Ralf Lammel
In a type system like MLF, your original code may type check.

Let's do an experiment.
We replace the IO monad by the Id(entity) monad.
We actually replace the Id newtype also to become true type-level
identity.
So we get:

--
-- This is like your 2nd say unchecked... sample
--

fooBar :: [v] - Empty
fooBar l = Empty (map no l)
 where
  no :: a - a'
  no x = error element found

But the problem is not about a higher-rank type occurring with a type
constructor, as you guess. It is rather about functions with classic
rank-1 types. To see this, insert $ for the application of Empty:

fooBar :: [v] - Empty
fooBar l = Empty $ (map no l)
 where
  no :: a - a'
  no x = error element found

You get the same type error as for the original monadic code. What you
could do is define a suitably typed application operator (likewise, a
suitably typed liftM). (With MLF the various types would be admitted by
a more general type.) In the non-monadic example, we need:

-- Use app instead of ($)
app :: ((forall a. [a]) - c) - (forall b. [b]) - c app f x = f x

BTW, what operations are we supposed to perform on the content of Empty;
what's the real purpose for introducing this independent type variable
a'? Parametric polymorphism seems to suggest that we can't do much.
You can observe the length of the list. That's it, more or less. Why not
store the length directly rather than having this superficially
polymorphic list? I am a little bit lost.

You wonder how you can generally solve this sort of problem?
- You seem to spot the wrapping approach: wrap foralls and unpack at
application time. This makes particularly sense for polymorphic
*functions*.
- The other approach is to use consistently rank-2 combinators.

I probably don't get what you try to do.

Ralf

 -Original Message-
 From: [EMAIL PROTECTED] [mailto:haskell-cafe- 
 [EMAIL PROTECTED] On Behalf Of Andrew Pimlott
 Sent: Thursday, November 03, 2005 8:35 PM
 To: haskell-cafe@haskell.org
 Subject: [Haskell-cafe] handling rank 2 types
 
 I am trying to use a rank 2 type to enforce a condition on a data 
 structure.  For the purpose of this message, I am trying to ensure 
 that a list is empty (ignoring the possibility of bottom elements):
 
  {-# OPTIONS -fglasgow-exts #-}
  import Control.Monad
  newtype Empty = Empty (forall a. [a])
 
 I want a function
 
  listToEmpty :: [v] - IO Empty
  listToEmpty l = liftM Empty (mapM no l) where
no :: a - IO a'
no x = fail element found
 
 But this gives a less polymorphic error.  I think the problem is 
 that ghc will not instantiate the a' in IO a' as a higher-rank 
 type because it occurs within a type contructor.  I believe this is 
 the restriction referred to at the end of 7.4.9[1].  If I instead 
 write
 
  uncheckedListToEmpty :: [v] - Empty uncheckedListToEmpty l = Empty 
  (map no l) where
no :: a - a'
no x = error element found
 
 it compiles, because v' can be instantiated as forall v. Rule v, 
 and even pass through map with the higher-rank type.
 
 Is there any way to make ghc accept the first definition?  I found 
 this
 workaround:
 
  newtype Any = Any { unAny :: forall a. a } listToEmptyAny :: [v] - 
  IO Empty listToEmptyAny l = liftM (\l - Empty (map unAny l)) (mapM 
  no l) where
no :: a - IO Any
no x = fail element found
 
 But needing a newtype wrapper Empty was bad enough; do I really need 
 one for every intermediate result (that is inside another type 
 constructor) as well?  I could probably define a generic family of 
 wrappers
 
  newtype Forall = Forall (forall a. a) newtype Forall1 c1 = Forall1 
  (forall a. c1 a) newtype Forall2 c1 c2 = Forall2 (forall a. c1 c2 a)
 ...
 
 But I would still have to use them everywhere.  Any other tricks?
 
 Andrew
 
 [1] http://haskell.org/ghc/docs/latest/html/users_guide/type-
 extensions.html#universal-quantification
 
 ___
 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