[Haskell-cafe] local loops

2004-12-14 Thread Per Larsson
I often use local loops in monadic code, e.g.

main = do
  ...
 let loop = do 
  ...
  if cond then loop else return () 
 loop

It seems that I can encode this idiom slightly more concise with the 'fix' 
operator (from Control.Monad.Fix), i.e.

main = do
   ...
   fix (\loop - do 
  ...
  if ...)

But is it really semantically equivalent? Is it as efficient? 

Per



  

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell] Implicit parameters

2004-06-09 Thread Per Larsson
When using implicit parameters I have noticed (at least for me) a rather 
puzzling behaviour with GHC and Hugs.

Given the declarations

data Env = Env {numlines :: Int, numcols  :: Int}

initEnv = Env {numlines = 0, numcols = 1}

withEnv :: ((?env :: Env) = IO a) - IO a
withEnv io = let ?env = initEnv in io

I can write code like:

main = withEnv (do
  let lines = numlines ?env
  putStrLn (Initial number of lines is  ++ (show lines)))

which works as expected, but the version below

main = withEnv $ do
  let lines = numlines ?env
  putStrLn (Initial number of lines is  ++ (show lines))

is not accepted by either GHC or Hugs! Is this a bug or have stumbled into a 
context where it actually matters if you use '$' or explicit grouping with 
parentheses?

Per Larsson


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


[Haskell-cafe] GHC and libc

2004-05-15 Thread Per Larsson
When I compile my haskell program (on a linux machine) with GHC and send it to 
a colleague he can't run it because he has a somewhat older version of libc. 
Is there a GHC switch that I have missed that enables you to statically link 
the parts of libc that is used by the haskell program? Alternatively have 
someone other tips for solving this problem? (I'm reluctant to force all my 
colleagues to install GHC, because of the size and long installation time, 
and I can't let them use Hugs because I've used some GHC-only features in my 
program.)

Per Larsson


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC and libc

2004-05-15 Thread Per Larsson
Thanks Duncan and Sven for your helpful answers. 

Per Larsson

P.S Now everything seems to work, except that I get the compiler message:
 
/usr/local/lib/ghc-6.2/libHSunix.a(User__17.o)(.text+0x160): In function
'SystemziPosixziUser_getUserEntryForName_entry':
: Using 'getpwnam_r' in statically linked applications requires at runtime the 
shared libraries from the glibc version used for linking

This seems to indicate that there are a few functions (probably in the Posix 
package) which can't be can't be statically linked?

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-27 Thread Per Larsson
In my humble opionon explicit module prefixes are a feature, which enhance 
code clarity, and not something you want get rid of using rather complex  
namespace extensions. However, as Alastair Reid's mail in this thread 
indicates there are weaknesses in haskell's export mechanism. But these would 
be far more easy to fix than introducing the suggested per type namespace 
extension. The present export list is also rather ugly from an aesthetic 
point of view, clottering the module header. I would love to see an, 
repeatable, explicit 'export' directive with similar keywords as the import 
directive. Allowing for example:
'export [all] hiding (...)' with obvious semantics.

Per Larsson

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


Re: [Haskell] regular expression syntax - perl ain't got nothin on haskell

2004-02-24 Thread Per Larsson
On Tuesday 24 February 2004 03.07, John Meacham wrote:
 Inspired by an idea by Andrew Pang and an old project of mine, I decided
 to fill out a reusable regular expression library which is similar to
 Perl's, but much more expressive.
  ...

Hi,
Thanks! I am grateful of your efforts because I have since long missed some 
typical text processing functionality in haskell. (Besides a more complete 
regular expression library I think many haskellers miss string constructors 
like an 'official' version of printf/format  and maybe also some sort of 
'here documents'.) Below follows some of my thoughts regarding a complete 
regex library, in the hope that this will be of any inspiration.

1. Replacement
A regex library must contain functions for replacement with regular 
expressions. One could think this is trivial to implement given a match 
function, but there are some tricky choices to be made regarding empty 
matches (this also applies to splitting a string into fields with a regexp). 
Also there is questions about the interface of these functions.
In my own Text.Regex wrapper I have the functions.

  data Match = Match {before :: String, after :: String, groups :: [String]}
  ...
  substWithPat :: Rexex - String - (Int - Bool) - String - (String,Int)
  substWithFun :: Regex - (Match-String) - (Int-Bool) - 
   String - (String,Int)
  substWithFunM :: (Monad m) = Regex - (Match - m String) - 
 (Int-Bool) - String - m (String,Int)

Where a call to 'substWithPat pat rpat mode str' replaces matches
of 'pat' in 'str' by 'rpat' and returns the resulting string and the number of 
replacements done. The 'rpat' replace pattern can contain backreferences on 
the form \m where \m refers to the mth subgroup in the corresponding match 
(\0 refers to the entire match). The call replaces only 'replaceable 
matches'.  A match m is replaceable if its the nth match and (mode n) is true 
and,  m is either the first match, a proper match or an empty match succeding 
an empty match. This schema gives results which are conformant with replace 
functionality in several other regex libraries, e.g. in Tcl, Python and Perl. 
For example, replacing matches of _* by _ in awk gives _a_w_k_, and 
replacing matches of _* by _ in sed_and_awk gives _s_e_d_a_n_d_a_w_k.  
(Compare the discussion in 'Mastering Regular Expressions', O'Reilly, pages 
187-188.) The functions substWithFun and substWithFunM are obvious variations 
on the substWithPat function.

2. Constructing regular expressions.
There is the well known problem that the backslash is used both as a string 
escape character and a regexp operator. I know of three approaches to the 
problem:
 a) Bite the bullet and, e.g. write regexps like  in order to match a
 
single backslash (e.g. as in emacs lisp).
b) Use a language extensions for 'raw' strings where the backslash is not 
interpreted (e.g. /regex/ in awk, rregex in python and {regex} in Tcl).
c) Use a different operator than the backslash in regular expressions, this 
has the benefit of not demanding a language extension, but is nonstandard on 
the negative side. 
There is also the problem with inserting string values in regular expressions. 
Appending with ++ is not particular convenient with complicated regexps 
because the result can be rather unreadable. I suppose we have to wait for a
standard implementation of printf in template haskell for this problem.

Cheers
Per









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


Re: [Haskell] regular expression syntax - perl ain't got nothin on haskell

2004-02-24 Thread Per Larsson
On Tuesday 24 February 2004 15.25, Johannes Waldmann wrote:
 Per Larsson wrote:
   .. I have since long missed some
 
  typical text processing functionality in haskell.

 it is often the case that people process text
 only because they have no better (structured and typed) way of
 representing their data...

I agree with your point in the general case. For serious parsing and pretty 
printing tasks there are great haskell libraries like Parsec and PrettyPrint.
But I can't see why the haskell user shouldn't also have access to concise 
text processing notations, e.g. regular expressions and printf, to be used 
in, e.g. short script-like programs?

Cheers 
Per 

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


[Haskell-cafe] Template Haskell question?

2004-02-11 Thread Per Larsson
I have written a small TH application (module THRecord) which creates update 
functions for records. It is intended to be used like this:

import THRecord

data Record = R {... 
...
$(THRecord.generateRecordModifiers (reifyDecl Record))

It works great, but only if the splice is placed last in the importing module! 
If I place it in the middle of the module it seems to hide subsequent 
declarations and I get 'Variable not in scope ...' compiler errors. If I 
place it at the top of the module I get:

ghc-6.2: panic! (the `impossible' happened, GHC version 6.2):
nameModule Record {- tc 01D -}

Has anybody a clue of what is happening here?

-- Per


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: FFI preprocessor for GHC

2004-01-15 Thread Per Larsson
Hello,

I would instead suggest greencard as a good preprocessor. It is portable in 
the sense that it outputs haskell code in accordance with the new FFI 
specification. Also, it has an input format which, in my opinion, is easier 
to learn and is better documented than hsc2hs. You can download the program 
and manual at:
http://haskell.org/greencard/

Per Larsson




On Thursday 15 January 2004 18.40, Jeremy Shaw wrote:
 Hello,

 One answer might be to not use a preprocessor at all. I found that I
 could not understand what the preprocessers where actually doing until
 I understood how to do it by hand. The nice thing about doing it by
 hand, is it is probably the most portable, since it does not require
 any preprocessor.

 On the otherhand, there is nothing wrong with using a preprocessor,
 and it can certainly save time. hsc2hs is included in the ghc source
 tree, so that would probably be my first choice.

 Jeremy Shaw.


 At Thu, 15 Jan 2004 18:18:11 +0100,

 Gour wrote:
  Hi!
 
  I'd like to create Haskell bindings for swisseph C library for
  calculating ephemeris.
 
  Which preprocessor would be a suitable for ghc compiler with the ability
  to run the code both on Linux  Win32?
 
  Sincerely,
  Gour
 
  --
  Gour
  [EMAIL PROTECTED]
  Registered Linux User #278493
 
  ___
  Haskell-Cafe mailing list
  [EMAIL PROTECTED]
  http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: getting the path to the executing program

2004-01-08 Thread Per Larsson
On Thursday 08 January 2004 18.06, Hal Daume III wrote:
 is there a function, related to getProgName, which returns the (absolute)
 path to the current program?

 basically, i want to be able to read a file which i know will be in the
 same directory as the current program, but not necessarily in the same
 directory that we're running it from.

I don't know how to do this in a portable way, but on unix/linux you can use 
the standard trick of reading the symbolic link
/proc/process-id/exe .

For example:

import System.Posix.Files  (readSymbolicLink)
import System.Posix.Process (getProcessID)

main = do
pid - getProcessID
path - readSymbolicLink (/proc/ ++ (show pid) ++ /exe)
putStrLn (Absolute path of this program is  ++ path)

PS. This doesn't work with interpreted code (Hugs, GHCi) in which case
you get the path to the interpreter itself.

Cheers
Per









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


Haddock and man pages

2004-01-02 Thread Per Larsson
Hi,

When you have a good understanding of a programming library  and only need to 
quickly refresh your memory regarding the type signature of a specific 
function, etc., I find man pages very convenient. Are there any plans of 
adding this  as an alternative output format in Haddock? If not, maybe I will 
try to write a patch when I find some spare time, but it would be encouraging 
to know  if this would interest anyone else but myself?

Cheers 
Per

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


Re: pretty newby

2003-09-23 Thread Per Larsson
On Tuesday 23 September 2003 16.05, Luc Taesch wrote:
 are there any facility to pretty print an haskell program ?
 im aware of HPJ combinators library, but i was looking for a command line
 utility, rather.. am i missing an entry in HPJ ?

 thanks
 Luc
 ___
 Haskell mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell

Hi,
In GHC (and HUGS?) you can use the 'haskell-src' package which contains
functions for parsing and pretty-printing haskell code. Using these, it only 
takes a couple of lines to make your own command line, pretty-printer for 
haskell code. If you want to, you can use my implementation which I attach to 
this mail. The problem with the parser, however, is that it doesn't handle 
comments at all.

Regards
Per-- FILE: HsIndent.hs
-- AUTH: Per Larsson
-- DATE: 03/10/2003
-- CODE: Haskell Code

module Main where

import System.Environment
import System.Exit
import System.IO
import Control.Monad
import Language.Haskell.Parser
import Language.Haskell.Pretty
import System.Console.GetOpt

header  = hsindent [OPTION ...] FILE
version = hsindent 1.0
usage   = usageInfo header options

data Config = Config {showHelp, showVersion :: Bool, pmode :: PPHsMode}
 
defaultConfig = Config False False defaultStyle

defaultStyle :: PPHsMode
defaultStyle = PPHsMode { 
classIndent = 8,
doIndent = 3,
caseIndent = 5,
letIndent = 4,
whereIndent = 6,
onsideIndent = 2,
spacing = True,
layout = PPOffsideRule,
linePragmas = False,
comments = True
  }

options :: [OptDescr (Config - Config)]
options = 
[ opt 'h' help print this help information and exit 
  (\c - c {showHelp = True}) 
, opt 'v' version print version information and exit
  (\c - c {showVersion = True})
, opt 'u' nospacing don't insert blank lines
  (\c - c {pmode = (pmode c) {spacing = False}})
, opt 'p' pragmas  insert source pragmas 
  (\c - c {pmode = (pmode c) {linePragmas = True}})
, opt 'e' comments  keep comments 
  (\c - c {pmode = (pmode c) {comments = True}}) 
, arg 's' class N indent class declarations N columns 
  (\s c - c {pmode = (pmode c) {classIndent = read s}})
, arg 'd' do N indent do expressions N columns
  (\s c - c {pmode = (pmode c) {doIndent = read s}}) 
, arg 'w' where N indent where expressions N columns 
  (\s c - c {pmode = (pmode c) {whereIndent = read s}})
, arg 'l' let N indent let expressions N columns
  (\s c - c {pmode = (pmode c) {letIndent = read s}})
, arg 'c' case N indent case expressions N columns 
  (\s c - c {pmode = (pmode c) {caseIndent = read s}})
, arg 'o' onside N indent at line continuations N columns 
  (\s c - c {pmode = (pmode c) {onsideIndent = read s}})
, arg 'y' layout  ARG set layout style to ARG, one of\n\
  \ 'OffsideRule', 'SemiColon', 'Inline' or 'NoLayout'
  (\s c - c {pmode = (pmode c) {layout = toLayout s}})  
] 
   where
   opt short long msg update = 
   Option [short] [long] (NoArg update) msg
   arg short long argdescr msg update = 
   Option [short] [long] (ReqArg update argdescr) msg
  
toLayout :: String - PPLayout
toLayout OffsideRule = PPOffsideRule
toLayout SemiColon   = PPSemiColon
toLayout InLine  = PPInLine
toLayout NoLayout= PPNoLayout
toLayout _ = error toLayout

--   

main = do 
args - getArgs
(conf,files) - case getOpt Permute options args of
(o,n,[])   - return (foldr ($) defaultConfig o, n)
(_,_,errs) - error (concat errs ++ usageInfo header options) 
when (showHelp conf) (exitSuccess usage)
when (showVersion conf) (exitSuccess version)
unless (length files == 1) (exitFail usage)
file - return (head files)
h - openFile file ReadMode
s - hGetContents h
result - return (parseModuleWithMode (ParseMode file) s)
case result of
ParseOk hsModule - 
exitSuccess (prettyPrintWithMode (pmode conf) hsModule)
ParseFailed pos msg - 
exitFail (Parse Error at:  ++ show pos ++ \n  ++ show msg)
where 
exitSuccess msg = (putStrLn msg  exitWith ExitSuccess)
exitFail msg = (putStrLn msg  exitFailure)
 


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


Re: Library documentation

2003-09-05 Thread Per Larsson
On Friday 05 September 2003 16.35, Konrad Hinsen wrote:
 Is there any place where I can find an introductory documentation for the
 Haskell libraries? To be more concrete, say I am interested in using
 Data.Array.ST.STUArray. I would need some explanation of the ST monad, and
 then an explanation of how I can use an STUArray in an ST monad. Plus
 ideally examples. But the same applies to most of the libraries. I can't
 find any documentation other than the very terse reference or the parts
 that happen to be covered by textbooks.

 Konrad.

I have the same problem and as far as I know there is only haddock generated 
html-documentation from sparse source comments available for many parts of 
the library. But for some of the modules you can get exactly the  information 
you are asking for, e.g. the Parsec module has its own readable documentation 
at http://www.cs.uu.nl/~daan/parsec.html and the Control.Monad module
has recently been superbly documented by John Newbern at 
http://www.nomaware.com/monads/html/.

Best Regards
Per

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Alex 2.0

2003-08-22 Thread Per Larsson
On Friday 22 August 2003 13.04, Immanuel Litzroth wrote:
 Has anyone an example of reg{n,k} regular expression in Alex 2.0?
 I can not get them to work, alex won't parse them (not the way I write
 them anyway)
 Immanuel


Hi,

Here comes a silly example which in any case 
works as expected on my linux system with alex and ghc.

file foo.x contains:

{
module Main (main) where
}

%wrapper basic

words :-

$white+ ;
A{3,5} { \s - () }

{
main = do
 s - getContents
 print (length (alexScanTokens s))
}
---

% alex foo.x
% ghc --make foo.hs
% a.out   testfile.txt

Regards Per
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Debugging

2003-03-28 Thread Per Larsson

I need to learn to use a debugging tool for haskell. There seems to be a whole 
bunch of them (Hood, Freja, Hat, Buddha, ...). Can anyone give me a 
(subjective) recommendation.

Thanks Per  
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


source layout

2003-03-06 Thread Per Larsson

Hi all,

I'm looking for some kind of style-guide for layout and indentation of haskell 
source code, can anyone help me?

Thanks, Per

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


Happy Alex

2003-02-28 Thread Per Larsson
I have successfully used the the excellent haskell tools Happy and Alex in a 
couple of parsing projects, but I have failed when trying to  combine a 
monadic Happy grammar (using the %monad and %lexer directives) together with 
an Alex generated okenizer, nor are there any such examples in the Happy and 
Alex distributions. Have anyone tried this combination and can give me some 
advice or a simple example?

-- 
Per 


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