[GHC] #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC.

GHC ghc-devs at haskell.org
Tue Jun 27 16:30:59 UTC 2017


#13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC.
-------------------------------------+-------------------------------------
           Reporter:  vanto          |             Owner:  (none)
               Type:  feature        |            Status:  new
  request                            |
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Other
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 I wrote this little piece of code to show that the compiler could very
 well execute the pragma by itself without being ordered to do so.\\

 {{{
 module Testfoo where
 import Language.Haskell.TH.Lib
 import Data.Kind

 tup = $(tupE $ take 4 $ cycle [ [| "hi" |] , [| 5 |] ])

 data T = MkT (forall a. [a] -> [a])

 answer_read = show (read @Int "3")

 data Foo (a :: Type) (b :: Type) where
   MkFoo :: (a ~ Int, b ~ Char) => Foo a b

 data family Song (a :: k)
 }}}
 By compiling the code without the Pragmas, GHC responds:\\

  * 1) c:\Testghc>ghc testfoo.hs
 [1 of 1] Compiling Testfoo          ( testfoo.hs, testfoo.o )

 testfoo.hs:13:7: error:
     parse error on input `$'
     Perhaps you intended to use TemplateHaskell\\
  * 2) c:\Testghc>ghc testfoo.hs
 [1 of 1] Compiling Testfoo          ( testfoo.hs, testfoo.o )

 testfoo.hs:15:23: error:
     Illegal symbol '.' in type
     Perhaps you intended to use {{{RankNTypes}}} or a similar language
     extension to enable explicit-forall syntax: forall <tvs>.<type>\\
  * 3) c:\Testghc>ghc testfoo.hs
 [1 of 1] Compiling Testfoo          ( testfoo.hs, testfoo.o )

 testfoo.hs:19:16: error:
     Illegal kind signature: `Type'
       Perhaps you intended to use KindSignatures
     In the data type declaration for `Foo'

 testfoo.hs:19:28: error:
     Illegal kind signature: `Type'
       Perhaps you intended to use KindSignatures
     In the data type declaration for `Foo'

 testfoo.hs:22:1: error:
     Unexpected kind variable `k' Perhaps you intended to use
 {{{PolyKinds}}}
 In the declaration for type family `Song'

 testfoo.hs:22:24: error:
     Illegal kind signature: `k'
       Perhaps you intended to use KindSignatures
     In the declaration for type family `Song'\\
  * 4) c:\Testghc>ghc testfoo.hs
 [1 of 1] Compiling Testfoo          ( testfoo.hs, testfoo.o )

 testfoo.hs:18:21: error:
     Pattern syntax in expression context: read at Int
     Did you mean to enable {{{TypeApplications}}}?\\
  * 5) c:\Testghc>ghc testfoo.hs
 [1 of 1] Compiling Testfoo          ( testfoo.hs, testfoo.o )

 testfoo.hs:20:1: error:
     * Illegal generalised algebraic data declaration for `Foo'
         (Use {{{GADTs}}} to allow GADTs)
     * In the data declaration for `Foo'\\
  * 6) c:\Testghc>ghc testfoo.hs
 [1 of 1] Compiling Testfoo          ( testfoo.hs, testfoo.o )

 testfoo.hs:23:1: error:
     * Illegal family declaration for `Song'
         Use {{{TypeFamilies}}} to allow indexed type families
     * In the data family declaration for `Song'\\
  * 7) c:\Testghc>ghc testfoo.hs
 [1 of 1] Compiling Testfoo          ( testfoo.hs, testfoo.o )

 c:\Testghc>\\

 Here is the code once completed.

 {{{
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE TypeApplications #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE TypeFamilies #-}

 module Testfoo where
 import Language.Haskell.TH.Lib
 import Data.Kind

 tup = $(tupE $ take 4 $ cycle [ [| "hi" |] , [| 5 |] ])

 data T = MkT (forall a. [a] -> [a])

 answer_read = show (read @Int "3")

 data Foo (a :: Type) (b :: Type) where
   MkFoo :: (a ~ Int, b ~ Char) => Foo a b

 data family Song (a :: k)
 }}}

 As you may notice, GHC suggests the appropriate pragma.\\
 If we add manually in the code the Pragmas one after the other and we
 arrive at the end, the code is fully compiled without error.\\
 The compiler could do this alone.\\
 We could test it using a "-auto" option on the compiler command line.\\
 This is a start to the compiler automation technology, what do you think
 of that?

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13884>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list