Re: [GHC] #3645: Layout and pragmas

2011-09-18 Thread GHC
#3645: Layout and pragmas
+---
  Reporter:  igloo  |  Owner:  
  Type:  feature request| Status:  new 
  Priority:  normal |  Milestone:  7.4.1   
 Component:  Compiler (Parser)  |Version:  6.10.4  
Resolution: |   Keywords:  
  Testcase: |  Blockedby:  
Difficulty:  Unknown| Os:  Unknown/Multiple
  Blocking: |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown   |  
+---
Changes (by igloo):

  * milestone:  7.2.1 => 7.4.1


Comment:

 One possibility is something along these lines:
 {{{
 diff --git a/compiler/main/HeaderInfo.hs b/compiler/main/HeaderInfo.hs
 index a3f7e79..738f4f8 100644
 --- a/compiler/main/HeaderInfo.hs
 +++ b/compiler/main/HeaderInfo.hs
 @@ -39,6 +39,7 @@ import Exception
  import Control.Monad
  import System.IO
  import System.IO.Unsafe
 +import Data.Char
  import Data.List

 --
 @@ -227,24 +228,31 @@ getOptions' toks
| ITdocOptionsOld str <- getToken open
= map (L (getLoc open)) ["-haddock-opts", removeSpaces str]
  ++ parseToks xs
 -  parseToks (open:xs)
 -  | ITlanguage_prag <- getToken open
 -  = parseLanguage xs
 +  parseToks (open:close:xs)
 +  | ITlanguage_prag str <- getToken open
 +  , ITclose_prag <- getToken close
 +  = parseLanguage (getLoc open) str
 +++ parseToks xs
parseToks (x:xs)
| ITdocCommentNext _ <- getToken x
= parseToks xs
parseToks _ = []
 -  parseLanguage (L loc (ITconid fs):rest)
 -  = checkExtension (L loc fs) :
 -case rest of
 -  (L _loc ITcomma):more -> parseLanguage more
 -  (L _loc ITclose_prag):more -> parseToks more
 -  (L loc _):_ -> languagePragParseError loc
 -  [] -> panic "getOptions'.parseLanguage(1) went past eof
 token
 -  parseLanguage (tok:_)
 -  = languagePragParseError (getLoc tok)
 -  parseLanguage []
 -  = panic "getOptions'.parseLanguage(2) went past eof token"
 +
 +  parseLanguage loc str
 +  = map (checkExtension loc) $ splits (dropWhile isSpace str)
 +  where isSepChar c = isSpace c || c == ','
 +splits [] = languagePragParseError loc
 +splits (',' : _) = languagePragParseError loc
 +splits xs0 = case break isSepChar xs0 of
 + (extension, xs1) ->
 + extension
 +   : (case dropWhile isSpace xs1 of
 +  ',' : xs2 ->
 +  splits (dropWhile isSpace xs2)
 +  [] ->
 +  []
 +  _ ->
 +  languagePragParseError loc)

 -

 @@ -263,14 +271,13 @@ checkProcessArgsResult flags

 -

 -checkExtension :: Located FastString -> Located String
 -checkExtension (L l ext)
 +checkExtension :: SrcSpan -> String -> Located String
 +checkExtension l ext
  -- Checks if a given extension is valid, and if so returns
  -- its corresponding flag. Otherwise it throws an exception.
 - =  let ext' = unpackFS ext in
 -if ext' `elem` supportedLanguagesAndExtensions
 -then L l ("-X"++ext')
 -else unsupportedExtnError l ext'
 + =  if ext `elem` supportedLanguagesAndExtensions
 +then L l ("-X" ++ ext)
 +else unsupportedExtnError l ext

  languagePragParseError :: SrcSpan -> a
  languagePragParseError loc =
 diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x
 index 90e1e66..754247b 100644
 --- a/compiler/parser/Lexer.x
 +++ b/compiler/parser/Lexer.x
 @@ -480,7 +480,7 @@ data Token
| ITclose_prag
| IToptions_prag String
| ITinclude_prag String
 -  | ITlanguage_prag
 +  | ITlanguage_prag String
| ITvect_prag
| ITvect_scalar_prag
| ITnovect_prag
 @@ -2233,7 +2233,7 @@ linePrags = Map.singleton "line" (begin line_prag2)
  fileHeaderPrags = Map.fromList([("options", lex_string_prag
 IToptions_prag),
   ("options_ghc", lex_string_prag
 IToptions_prag
   ("options_haddock", lex_string_prag
 ITdocOptio
 -   

Re: [GHC] #3645: Layout and pragmas

2011-04-08 Thread GHC
#3645: Layout and pragmas
+---
  Reporter:  igloo  |  Owner:  
  Type:  feature request| Status:  new 
  Priority:  normal |  Milestone:  7.2.1   
 Component:  Compiler (Parser)  |Version:  6.10.4  
Resolution: |   Keywords:  
  Testcase: |  Blockedby:  
Difficulty:  Unknown| Os:  Unknown/Multiple
  Blocking: |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown   |  
+---
Changes (by igloo):

  * status:  patch => new


Comment:

 I'm not sure what the spec is.

 Should this be rejected (as the `#-}` starts a new decl)?
 {{{
 foo = 'a'

 {-# INLINE bar
 #-}
 bar = 'b'
 }}}

 Should this be rejected (as the `{-#` decl doesn't have the correct
 indentation)?
 {{{
 foo = 'a'

{-# INLINE bar #-}
 bar = 'b'
 }}}

 The `INLINE` pragma looks like a declaration, but the `SCC` pragma looks
 like an expression, so how about this?:
 {{{
 foo = {-# SCC bar
 #-} 'a'
 }}}
 ?

 Should the layout rule apply to the `LANGUAGE` pragma in any way? I assume
 not, as we haven't had the `where` from the `module` line yet.

 IMO, the particular bug in this ticket is that GHC thinks it is doing
 implicit layout, when it shouldn't be.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3645: Layout and pragmas

2010-12-14 Thread GHC
#3645: Layout and pragmas
--+-
Reporter:  igloo  |Owner:  
Type:  feature request|   Status:  patch   
Priority:  normal |Milestone:  7.0.1   
   Component:  Compiler (Parser)  |  Version:  6.10.4  
Keywords: | Testcase:  
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by michalt):

 Replying to [comment:9 boris]:
 > You are right, \n"#-}" is not enough. I missed the case when several \n
 occur.
 > Function lexToken calls alexScanUser, so it should match some tokens,
 should
 > not it? I am new to Alex and can be mistaken. Can you explain why it
 does not
 > match any tokens?

 Sorry for confusion, I meant that `lexTokens` only checks for eof/errors
 and
 calls an appropriate action to create token, but does not really directly
 inspect the input (it just uses `alexScanUser`). And that's why I don't
 think it
 is the right place to put some special case for closing the pragma.

 Anyway, I guess the best thing right now is to wait for some GHC dev to
 have a
 look at this.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3645: Layout and pragmas

2010-12-14 Thread GHC
#3645: Layout and pragmas
--+-
Reporter:  igloo  |Owner:  
Type:  feature request|   Status:  patch   
Priority:  normal |Milestone:  7.0.1   
   Component:  Compiler (Parser)  |  Version:  6.10.4  
Keywords: | Testcase:  
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by boris):

 You are right, \n"#-}" is not enough. I missed the case when several \n
 occur.
 Function lexToken calls alexScanUser, so it should match some tokens,
 should not it? I am new to Alex and can be mistaken. Can you explain why
 it does not match any tokens?

 It would be nice to allow entering into bol state on \n(as before any
 patches) and exit it on some condition(without hardcoding "#-}") so that
 "#-}" can be matched. If it is not possible, I support the whitespace
 solution.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3645: Layout and pragmas

2010-12-13 Thread GHC
#3645: Layout and pragmas
--+-
Reporter:  igloo  |Owner:  
Type:  feature request|   Status:  patch   
Priority:  normal |Milestone:  7.0.1   
   Component:  Compiler (Parser)  |  Version:  6.10.4  
Keywords: | Testcase:  
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by michalt):

 What do you mean redundant? Example:
 {{{
 {-# LANGUAGE EmptyDataDecls
, DeriveDataTypeable

 #-}

 module Foo where

 import Data.Typeable

 data Test = Test
   deriving (Typeable)
 }}}
 With
 {{{
   "#-}"{ endPrag }
   \n"#-}"  { endPrag }
 }}}
 I'm getting:
 {{{
 Test.hs:2:14:
 Cannot parse LANGUAGE pragma
 Expecting comma-separated list of language options,
 each starting with a capital letter
   E.g. {-# LANGUAGE RecordPuns, Generics #-}
 }}}
 And with
 {{{
   $whitechar* "#-}"  { endPrag }
 }}}
 It compiles just fine.

 Also I'm really not convinced that it should be `lexToken` to match the
 closing.
 After all this function doesn't really match any actual tokens - it just
 checks
 for lexing errors/eof, updates lexer state, etc.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3645: Layout and pragmas

2010-12-13 Thread GHC
#3645: Layout and pragmas
--+-
Reporter:  igloo  |Owner:  
Type:  feature request|   Status:  patch   
Priority:  normal |Milestone:  7.0.1   
   Component:  Compiler (Parser)  |  Version:  6.10.4  
Keywords: | Testcase:  
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by boris):

 Matching all whitespaces is redundant, although it looks not as hacky.
 Normally whitespaces are matched in another place. We have to match \n
 only to prevent entering into bol state. I did some more tracing and found
 that in function do_bol clause

 {{{
 GT -> do
 _ <- popLexState
 lexToken
 }}}

 is executed. I think that in proper solution lexToken should match "#-}"
 and close the pragma.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3645: Layout and pragmas

2010-12-11 Thread GHC
#3645: Layout and pragmas
--+-
Reporter:  igloo  |Owner:  
Type:  feature request|   Status:  patch   
Priority:  normal |Milestone:  7.0.1   
   Component:  Compiler (Parser)  |  Version:  6.10.4  
Keywords: | Testcase:  
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-
Changes (by michalt):

 * cc: michal.terep...@… (added)
  * status:  new => patch


Comment:

 I'm not sure if this is the right approach either. But if it is, I'd
 prefer to ensure that we match any number of newlines/whitespace..

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3645: Layout and pragmas

2010-12-10 Thread GHC
#3645: Layout and pragmas
--+-
Reporter:  igloo  |Owner:  
Type:  feature request|   Status:  new 
Priority:  normal |Milestone:  7.0.1   
   Component:  Compiler (Parser)  |  Version:  6.10.4  
Keywords: | Testcase:  
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by boris):

 Please, review the patch.
 The problem was that line

 {{{
 <0,option_prags> \n { begin bol }
 }}}

 switched alex state to to ''bol''. If there is space between newline and
 "#-}", the previous state is popped in do_bol function and end of pragma
 successfully matches in ''option_prags'' state. But without any space the
 beginning of "#-}" will be matched in ''bol'' state and the rest will fail
 to match.

 Perhaps the patch is a little hacky and it is better to modify bol part.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3645: Layout and pragmas

2009-11-17 Thread GHC
#3645: Layout and pragmas
+---
  Reporter:  igloo  |  Owner:  
  Type:  feature request| Status:  new 
  Priority:  normal |  Milestone:  6.14.1  
 Component:  Compiler (Parser)  |Version:  6.10.4  
Resolution: |   Keywords:  
Difficulty:  Unknown| Os:  Unknown/Multiple
  Testcase: |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown   |  
+---
Changes (by guest):

  * failure:  => None/Unknown
  * type:  bug => feature request

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3645: Layout and pragmas

2009-11-07 Thread GHC
#3645: Layout and pragmas
--+-
Reporter:  igloo  |Owner:  
Type:  bug|   Status:  new 
Priority:  normal |Milestone:  6.14.1  
   Component:  Compiler (Parser)  |  Version:  6.10.4  
Severity:  normal |   Resolution:  
Keywords: |   Difficulty:  Unknown 
Testcase: |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   |  
--+-
Changes (by eflister):

 * cc: erik.flis...@gmail.com (added)

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3645: Layout and pragmas

2009-11-07 Thread GHC
#3645: Layout and pragmas
--+-
Reporter:  igloo  |Owner:  
Type:  bug|   Status:  new 
Priority:  normal |Milestone:  6.14.1  
   Component:  Compiler (Parser)  |  Version:  6.10.4  
Severity:  normal |   Resolution:  
Keywords: |   Difficulty:  Unknown 
Testcase: |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   |  
--+-
Comment (by eflister):

 whoops, to be really explicit, i should include a comment example:

 {{{
 {-# LANGUAGE
   EmptyDataDecls
 , MultiParamTypeClasses
 --  , RecordPuns
 , Generics
 --  , DeriveDataTypeable
 , FlexibleContexts
 #-}
 }}}

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3645: Layout and pragmas

2009-11-07 Thread GHC
#3645: Layout and pragmas
--+-
Reporter:  igloo  |Owner:  
Type:  bug|   Status:  new 
Priority:  normal |Milestone:  6.14.1  
   Component:  Compiler (Parser)  |  Version:  6.10.4  
Severity:  normal |   Resolution:  
Keywords: |   Difficulty:  Unknown 
Testcase: |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   |  
--+-
Comment (by eflister):

 just to be super pedantic, i want to make sure the following would be ok
 too.  :)  afaik, lots of people use this kind of layout to make toggling
 lines via comments as easy as possible.

 {{{
 {-# LANGUAGE
   EmptyDataDecls
 , MultiParamTypeClasses
 #-}
 }}}

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #3645: Layout and pragmas

2009-11-07 Thread GHC
#3645: Layout and pragmas
+---
  Reporter:  igloo  |  Owner:  
  Type:  bug| Status:  new 
  Priority:  normal |  Milestone:  6.14.1  
 Component:  Compiler (Parser)  |Version:  6.10.4  
  Severity:  normal |   Keywords:  
Difficulty:  Unknown|   Testcase:  
Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple
+---
 With this module:
 {{{
 {-# LANGUAGE DeriveDataTypeable,
  FlexibleContexts
 #-}

 module Foo where
 }}}
 GHC 6.12 says:
 {{{
 Cannot parse LANGUAGE pragma
 Expecting comma-separated list of language options,
 each starting with a capital letter
   E.g. {-# LANGUAGE RecordPuns, Generics #-}
 }}}
 but this should probably be allowed. See #3519, #3616.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs