Re: looking for System.Console.Readline example

2003-12-02 Thread sebc

A minor modification to Martin's code gives you laziness:

> import System.IO.Unsafe
> import System.Console.Readline
> 
> readlines :: String -> IO [String]
> readlines prompt =
> do input <- readline prompt
>case input of
>Nothing ->
>return []
>Just str ->
>do strs <- unsafeInterleaveIO (readlines prompt)
>   return (str:strs)

*R> readlines ">" >>= mapM (print . length)
>foo
3
>barbaz
6

From the libraries documentation:

unsafeInterleaveIO :: IO a -> IO a 

unsafeInterleaveIO allows IO computation to be deferred lazily. When
passed a value of type IO a, the IO will only be performed when the
value of the a is demanded. This is used to implement lazy file
reading, see hGetContents.

-- 
Sebastien

On Tue, Dec 02, 2003 at 03:34:58PM +0100, Johannes Waldmann wrote:
> Martin Norbäck wrote:
> 
> >What do you mean? Readline is for editing one line. 
> 
> well, yes and no. sure its built-in history functions
> precisely do help editing a sequence of lines?
> as used in bash, ghci, hugs?
> 
> 
> I now have something that works (bottom of this file):
> 
> http://theo1.informatik.uni-leipzig.de/cgi-bin/cvsweb/autotool/Exp/Loop.hs?rev=1.3
> 
> 
> Still I think it would be nice to have
> 
> Readline.getContents :: IO String
> 
> that just returns the lazy input list
> (line by line, as getContents would do).
> 
> It's just another kind of line buffering,
> and this should be transparent to the application.
> (Of course, it couldn't change the prompt symbol then,
> but I could live with that).
> 
> -- 
> -- Johannes Waldmann,  Tel/Fax: (0341) 3076 6479 / 6480 --
> -- http://www.imn.htwk-leipzig.de/~waldmann/ -
> 
> 
> ___
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell


signature.asc
Description: Digital signature
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: System.Posix (symbolic links)

2003-11-29 Thread sebc

You need to use getSymbolicLinkStatus instead of getFileStatus, which
always follows symbolic links (I guess getSymbolicLinkStatus uses the
stat system call, while getSymbolicLinkStatus uses lstat).

-- 
Sebastien

On Sat, Nov 29, 2003 at 08:24:08PM +0100, Johannes Goetz wrote:
> Hi! Sorry for posting this message twice. Last message had wrong subject.
> 
> Calling isSymbolicLink always returns False... (ghc-6.0.1linux binary 
> tarball)
> It doesn't make a difference whether the symbolic link points
> to a regular file or a directory.
> Test code:
> 
> #ln -s test link
> #ghc Test.hs -o test
> #./test
> False
> #
> 
> Test.hs:
> 
> module Main(main) where
> import System.Posix
> main = do
> status <- getFileStatus "link"
> print (isSymbolicLink status)
> 
> 
> Johannes
> 
> ___
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell


signature.asc
Description: Digital signature
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Why are strings linked lists?

2003-11-28 Thread sebc
On Fri, Nov 28, 2003 at 12:37:30PM +0100, Wolfgang Jeltsch wrote:
> >
> > So, what is happening that there is 1 cell in the heap
> > containing the representation of 'a', and then a linked list
> > of length 500, where each element points to that cell.
> 
> Yes, you're right. But if you choose the array alternative, you cannot use 
> sharing and would, therefore, still need 20 MB.

You can use sharing if you don't use unboxed arrays.  Not that it
matters if a character takes as much space as a pointer, but for
64-bits floating point numbers on a platform with 32-bits pointers, it
would decrease memory consumption by almost half.
Anyway, I'm just nitpicking. :-)

-- 
Sebastien

signature.asc
Description: Digital signature
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: lifting functions to tuples?

2003-11-19 Thread sebc

Again, I think what you propose is different from what was asked.

> On 2003-11-18 at 10:46EST "Abraham Egnor" wrote:
> > The classic way to write a lift function for tuples is, of course:
> >
> > liftTup f (a, b) = (f a, f b)
> >
> > which has a type of (a -> b) -> (a, a) -> (b, b).  I've been wondering if
> > it would be possible to write a function that doesn't require the types in
> > the tuple to be the same, just that the types in the second tuple are the
> > result of applying the type transformation implied in the function to be
> > lifted to the types in the first tuple.

On Wed, Nov 19, 2003 at 05:25:19PM -0800, [EMAIL PROTECTED] wrote:
> 
> *Main> :t liftp
> forall a2 a a3 a1.
> (Typeable a, Typeable a1, Typeable a2, Typeable a3) =>
> (Dynamic -> Dynamic) -> (a1, a3) -> (a, a2)

Here there is no visible relation between the types in the first tuple
and the types in the second tuple.  The ``type transformation implied
in the function to be lifted'' is not reflected in the type of liftp.

I think an example of what Abraham Egnor asked for is:

> f1 :: a -> Maybe a
> f1 x = Just x

with desired type (Maybe Int, Maybe Bool) for the expression
liftTup f1 (1, True).

Yet another example is

> data T a = T (a, a -> T a)
> 
> f2 :: T a -> T a
> f2 (T (repr, m)) = m repr

with desired type (T a, T b) -> (T a, T b) for liftTup f2, so that
one can for example have

> o1 :: Int -> T Int
> o1 x = T (x, \ x -> o1 (x * 2))
> 
> o2 :: Float -> T Float
> o2 x = T (x, \ x -> o2 (x * 2.0))
> 
> v = liftTup f2 (o1 1, o2 1.0)

One could expect v to have type (T Int, T Float), but I don't think
the type system of Haskell can handle these simple, uncontrived
examples.  I don't intend this as a criticism, merely a fact.

Of course, one can always defeat the static type system when it gets
in the way, using Dynamics, as you demonstrated.

-- 
Sebastien



signature.asc
Description: Digital signature
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: lifting functions to tuples?

2003-11-19 Thread sebc
On Tue, Nov 18, 2003 at 05:56:19PM -0800, [EMAIL PROTECTED] wrote:
> 
> Abraham Egnor wrote:
> 
> > The classic way to write a lift function for tuples is, of course:
> 
> > liftTup f (a, b) = (f a, f b)
> 
> > which has a type of (a -> b) -> (a, a) -> (b, b).  I've been wondering if
> > it would be possible to write a function that doesn't require the types in
> > the tuple to be the same, just that the types in the second tuple are the
> > result of applying the type transformation implied in the function to be
> > lifted to the types in the first tuple.
> 
> Well, it is possible in Haskell. It works even in Hugs!
> 
> {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}
> 
> 
> class Funnable a b | a->b where
> f:: a -> b
> 
> instance Funnable Bool Int where
> f = fromEnum
> instance Funnable Char Float where
> f = fromRational . toRational . fromEnum
>  
> class LP a b c d where
> liftf:: (a, b) -> (c, d)
> 
> instance (Funnable a c, Funnable b d) => LP a b c d where
> liftf (a,b) = (f a, f b)
> 
> Main> liftf (True,'z')
> (1,122.0)

This seems different from what Abraham Egnor asked for, because it
allows one to provide many different implementations for f.
It corresponds more closely to

> liftTup' (f1, f2) (a, b) = (f1 a, f2 b)

which is of course typable with in Haskell.

Main> liftTup' (fromEnum, fromRational . toRational . fromEnum) (1, 122.0)
(1,122.0)

-- 
Sebastien

signature.asc
Description: Digital signature
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: lifting functions to tuples?

2003-11-18 Thread sebc
On Tue, Nov 18, 2003 at 04:34:43PM +, Jon Fairbairn wrote:
> On 2003-11-18 at 10:46EST "Abraham Egnor" wrote:
> > The classic way to write a lift function for tuples is, of course:
> > 
> > liftTup f (a, b) = (f a, f b)
> > 
> > which has a type of (a -> b) -> (a, a) -> (b, b).  I've been wondering if
> > it would be possible to write a function that doesn't require the types in
> > the tuple to be the same, just that the types in the second tuple are the
> > result of applying the type transformation implied in the function to be
> > lifted to the types in the first tuple.  
> 
> What you want is that f be applicable to both b and c,
> giving results b' and c', but if b and c happen to be the
> same type then f need not be polymorphic.
> 
> I don't think you can express this in ghc's type system. You'd have
> to have bounded quantification:
> 
> lifTup ::
> forall c, a >= c, b >= c, d, a'<=d, b'<= d. (c -> d) -> (a,b)->(a',b')

It can also be straightforwardly expressed in a type system that has
intersection types:

liftTup :: ((b -> b') ^ (c -> c')) -> (b, c) -> (b', c')

where '^' is the intersection type constructor.  That is in fact the
principal typing for liftTup, and it can be automatically inferred.

-- 
Sebastien

signature.asc
Description: Digital signature
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell