RE: literate scripts.

2003-08-14 Thread Simon Marlow
 
 Ghc should not accept this code, because, no matter how the 
 unliterating
 is achieved, it is illegal for a literal string to contain a 
 literal newline character.

Known bug in GHC.  In the testsuite, but unfortunately not documented.

Cheers,
Simon

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


Re: literate scripts.

2003-08-14 Thread Malcolm Wallace
Immanuel Litzroth [EMAIL PROTECTED] writes:

 thanks for your code. Perhaps I was not completely clear in my
 question: I specifically want to know if unliterating should include
 lexing so that it recognizes strings (comments) or if it can be a
 separate phase. The following compiles without problems in ghc.
 
 \begin{code}
 main :: IO ()
 main =  putStr 
 \end{code}
  
 \begin{code}
 
 \end{code}

Ghc should not accept this code, because, no matter how the unliterating
is achieved, it is illegal for a literal string to contain a literal newline
character.  (You must use '\n' for the character, and/or string-gaps if your
intention is to make the layout more readable.)

 The report says
  Program code ends just before a subsequent line that begins
  \end{code} (ignoring string literals, of course). 

Certainly if the unliteration spec in the Haskell 1.2 Report is still
valid (?) I believe the intention is that all unliteration is done
in a line-by-line manner before any interpretation of the code text.
Therefore, the unliteration engine does not need to lex the program
code at all.

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


Re: literate scripts.

2003-08-05 Thread Malcolm Wallace
Immanuel Litzroth [EMAIL PROTECTED] writes:

 I have a small question relating to literate haskell programs that
 use the \begin{code} \end{code} style. Am I correct to assume that 
 \end{code} inside a string should be recognized as being inside a
 string. The report seems to say this, but the unlit that is
 distributed with ghc doesn't grok this. Has anyone written an Unlit
 module in Haskell?

I have attached the Unlit.hs module from the nhc98 compiler, based
on the original specification in the the Haskell 1.2 Report.  Use the
exported function
unlit :: String - String - String
whose first argument is the filename (for error messages), the second
argument is the file content, and whose result is the un-literated
file.

Regards,
Malcolm
module Unlit(unlit) where

-- Part of the following code is from
-- Report on the Programming Language Haskell,
--   version 1.2, appendix C.

import Char

data Classified = Program String | Blank | Comment
| Include Int String | Pre String

classify :: [String] - [Classified]
classify []= []
classify (('\\':x):xs) | x == begin{code} = Blank : allProg xs
   where allProg [] = []  -- Should give an error message,
  -- but I have no good position information.
 allProg (('\\':x):xs) |  x == end{code} = Blank : classify xs
 allProg (x:xs) = Program x:allProg xs
classify (('':x):xs)  = Program (' ':x) : classify xs
classify (('#':x):xs)  = (case words x of
(line:file:_) | all isDigit line
   - Include (read line) file
_  - Pre x
 ) : classify xs
classify (x:xs) | all isSpace x = Blank:classify xs
classify (x:xs) = Comment:classify xs

unclassify :: Classified - String
unclassify (Program s) = s
unclassify (Pre s) = '#':s
unclassify (Include i f) = '#':' ':show i ++ ' ':f
unclassify Blank   = 
unclassify Comment = 

unlit :: String - String - String
unlit file lhs = (unlines
 . map unclassify
 . adjecent file (0::Int) Blank
 . classify) (inlines lhs)

adjecent :: String - Int - Classified - [Classified] - [Classified]
adjecent file 0 _ (x  :xs) = x : adjecent file 1 x xs -- force 
evaluation of line number
adjecent file n y@(Program _) ([EMAIL PROTECTED]  :xs) = error (message file n 
program comment)
adjecent file n y@(Program _) (x@(Include i f):xs) = x: adjecent fi y xs
adjecent file n y@(Program _) (x@(Pre _)  :xs) = x: adjecent file (n+1) y xs
adjecent file n [EMAIL PROTECTED] (x@(Program _)  :xs) = error (message file n 
comment program)
adjecent file n [EMAIL PROTECTED] (x@(Include i f):xs) = x: adjecent fi y 
xs
adjecent file n [EMAIL PROTECTED] (x@(Pre _)  :xs) = x: adjecent file (n+1) y 
xs
adjecent file n [EMAIL PROTECTED]   (x@(Include i f):xs) = x: adjecent fi 
y xs
adjecent file n [EMAIL PROTECTED]   (x@(Pre _)  :xs) = x: adjecent file (n+1) 
y xs
adjecent file n _ ([EMAIL PROTECTED] :xs) = x: adjecent file (n+1) 
x xs
adjecent file n _ []= []

message \\ n p c = Line ++show n++: ++p++  line before ++c++ line.\n
message [] n p c = Line ++show n++: ++p++  line before ++c++ line.\n
message file   n p c = In file  ++ file ++  at line ++show n++: ++p++  line 
before ++c++ line.\n


-- Re-implementation of 'lines', for better efficiency (but decreased laziness).
-- Also, importantly, accepts non-standard DOS and Mac line ending characters.
inlines s = lines' s id
  where
  lines' [] acc = [acc []]
  lines' ('\^M':'\n':s) acc = acc [] : lines' s id  -- DOS
  lines' ('\^M':s)  acc = acc [] : lines' s id  -- MacOS
  lines' ('\n':s)   acc = acc [] : lines' s id  -- Unix
  lines' (c:s)  acc = lines' s (acc . (c:))



literate scripts.

2003-08-05 Thread Immanuel Litzroth
I have a small question relating to literate haskell programs that
use the \begin{code} \end{code} style. Am I correct to assume that 
\end{code} inside a string should be recognized as being inside a
string. The report seems to say this, but the unlit that is
distributed with ghc doesn't grok this. Has anyone written an Unlit
module in Haskell?
Immanuel

***
It makes me uncomfortable to see
An English spinster of the middle class
Describe the amorous effects of `brass',
Reveal so frankly and with such sobriety
The economic basis of society.
W.H. Auden

--
Immanuel Litzroth
Software Development Engineer
Enfocus Software
Kleindokkaai 3-5
B-9000 Gent
Belgium
Voice: +32 9 269 23 90
Fax : +32 9 269 16 91
Email: [EMAIL PROTECTED]
web : www.enfocus.be
***

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


Re: Typesetting literate scripts in TeX

2001-12-14 Thread Marcin 'Qrczak' Kowalczyk

 Recently I've hacked up a (yet another) TeX package for typesetting
 literate scripts in TeX

Cool! I will use it in my thesis.

One bug: a line can be broken between an inline code and a comma
which immediately follows it.

-- 
 __(  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^
QRCZAK

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



Typesetting literate scripts in TeX

2001-12-13 Thread Patryk Zadarnowski


Recently I've hacked up a (yet another) TeX package for typesetting
literate scripts in TeX, which, I think belongs in
http://haskell.org/libraries/#tex;. What's different about lambdaTeX
is that it is not a cumbersome preprocessor, but a full TeX program
(an almost-complete Haskell lexical analyzer written entirely in 
plain TeX ;-) which typesets Bird-style literate scripts _directly_.
The output looks much like the code from Chris Okasaki's book Purely
Functional Data Structures, doing syntax highlighting and converting
ASCII art such as - or alpha to proper mathematical symbols.
It should work with both LaTeX and plain TeX, and it does its magic
without any annotations, directly on the source code (the only thing
that you will probably want to do is add \input lambdaTeX at the top
of your source file, and manually typeset your literate comments so they
look as good as the source code ;-)

I've got a rudimentary web page for it at http://www.jantar.org/lambdaTeX/
with examples and a summary of features. If you have any comments or
suggestions, I wouldn't mind hearing them.

Enjoy.

Pat.


-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
Patryk ZadarnowskiUniversity of New South Wales
[EMAIL PROTECTED] School of Computer Science and Engineering
-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-

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



FW: Literate scripts not handled correctly

2001-09-24 Thread Simon Peyton-Jones

Folks,

Back to the H98 grindstone:

  Then I think hugs and nhc98 are wrong.  The report states that the 
  unliterate version of the file is recovered by taking only
 those lines
  beginning with '', and removing the first character of
 those lines,
  which would leave the lines indented by a single space, not two.
 
 This would appear to be an un-remarked change to the Report since 
 version 1.2.  That version states that program lines have the leading

 '' replaced by a leading space, to preserve tab alignments. Version 
 1.3 removed this specification, and the changed specification only 
 appeared in Haskell'98.

This does indeed seem peculiar.  I propose to revert to the
Haskell 1.2 story, in which 

'' is replaced by ' '  (not simply deleted)

Not a big issue.  Any objections?

Simon

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



RE: Literate scripts not handled correctly

2001-09-18 Thread Simon Marlow

  Then I think hugs and nhc98 are wrong.  The report states that the
  unliterate version of the file is recovered by taking only 
 those lines
  beginning with '', and removing the first character of 
 those lines,
  which would leave the lines indented by a single space, not two.
 
 This would appear to be an un-remarked change to the Report since
 version 1.2.  That version states that program lines have the
 leading '' replaced by a leading space, to preserve tab alignments.
 Version 1.3 removed this specification, and the changed specification
 only appeared in Haskell'98.
 
 I would like to submit it as a bug in the Report - the older
 specification, as implemented by Hugs and nhc98 makes more sense in
 conjunction with the layout rule.

I'm inclined to agree.  But I'd like to know what the reason for the
change in the first place was.

GHC's unlit preprocessor converts the tabs to spaces in such a way that
they line up after removal of the '' characters, by the way.

Cheers,
Simon

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Literate scripts not handled correctly

2001-09-18 Thread Ian Lynagh


Hi all

My understanding is that the following script:

- cut here -

 foo :: Int - Int
 foo _ = 2

\begin{code}

bar :: Int - Int
bar _ = 1

\end{code}

- cut here -

should be valid and define foo and bar (although the report does say It
is not advisable to mix these two styles in the same file).

However, in hugs:
ERROR Q.lhs:7 - Syntax error in input (unexpected symbol bar)

% ghc -c -o Q.o Q.lhs
Q.lhs:7: parse error on input `bar'

% nhc98 -c -o Q.o Q.lhs 
In file ./Q.lhs:
7:1 Found bar but expected a {-EOF-}



Secondly, in the following script (which I think should define main
according to the report):

- cut here -

\begin{code}

module Main where

main :: IO()
main = putStrLn Foo

\end{code}

- cut here -

hugs:
ERROR W.lhs:12 - Empty script - perhaps you forgot the `'s?

% nhc98 -c -o W.o W.lhs
Warning: Can not find main in module Main.

ghc -c -o W.o W.lhs 
W.lhs line 11: unlit: missing \end{code}

Interestingly it works in GHC if you remove the white space before the
end but not before the begin.


Thanks
Ian


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



RE: Literate scripts not handled correctly

2001-09-18 Thread Simon Marlow


 My understanding is that the following script:
 
 - cut here -
 
  foo :: Int - Int
  foo _ = 2
 
 \begin{code}
 
 bar :: Int - Int
 bar _ = 1
 
 \end{code}
 
 - cut here -
 
 should be valid and define foo and bar (although the report 
 does say It
 is not advisable to mix these two styles in the same file).
 
 However, in hugs:
 ERROR Q.lhs:7 - Syntax error in input (unexpected symbol bar)

This is probably due to layout.  The unliterate version of the file
would be

 foo :: Int - Int
 foo _ = 2

bar :: Int - Int
bar _ = 1

so the occurrence of the token 'bar' at a column less than that of the
first 'foo' causes a close brace to be inserted by the layout system,
closing the top-level declaration group.

 Secondly, in the following script (which I think should define main
 according to the report):
 
 - cut here -
 
 \begin{code}
 
 module Main where
 
 main :: IO()
 main = putStrLn Foo
 
 \end{code}
 
 - cut here -
 
 hugs:
 ERROR W.lhs:12 - Empty script - perhaps you forgot the `'s?
 
 % nhc98 -c -o W.o W.lhs
 Warning: Can not find main in module Main.
 
 ghc -c -o W.o W.lhs 
 W.lhs line 11: unlit: missing \end{code}
 
 Interestingly it works in GHC if you remove the white space before the
 end but not before the begin.

Yes, it looks like GHC's unlit program removes whitespace when looking
for \begin{code}, but not for \end{code}.  The report isn't explicit
about whether whitespace is allowed on these lines, but I would tend to
the view that it isn't.

Cheers,
Simon

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Re: Literate scripts not handled correctly

2001-09-18 Thread Malcolm Wallace


 My understanding is that the following script:
 
 - cut here -
 
  foo :: Int - Int
  foo _ = 2
 
 \begin{code}
 
 bar :: Int - Int
 bar _ = 1
 
 \end{code}
 
 - cut here -
 
 should be valid and define foo and bar (although the report does say It
 is not advisable to mix these two styles in the same file).

The definitions of foo and bar are not at the same indentation level,
so they are being rejected by the layout rule.  At least, hugs and
nhc98 accept it if you indent bar by two spaces, ghc still complains:

  ghc -c lit.lhs
  lit.lhs:9: parse error on input `_'


Regards,
Malcolm

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



RE: Literate scripts not handled correctly

2001-09-18 Thread Simon Marlow

 The definitions of foo and bar are not at the same indentation level,
 so they are being rejected by the layout rule.  At least, hugs and
 nhc98 accept it if you indent bar by two spaces, ghc still complains:
 
   ghc -c lit.lhs
   lit.lhs:9: parse error on input `_'

Then I think hugs and nhc98 are wrong.  The report states that the
unliterate version of the file is recovered by taking only those lines
beginning with '', and removing the first character of those lines,
which would leave the lines indented by a single space, not two.

Cheers,
Simon

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs