Haskell Extensions in various compilers (Cabal)

Isaac Jones ijones at syntaxpolice.org
Mon Jul 12 23:14:58 EDT 2004


I've implemented a mapping[1] between compiler extensions and
command-line flags in Cabal[2] for GHC, NHC98, and Hugs.  Can some
representatives from each take a look at these and let me know if I'm
wrong about how any of them work, whether I missed support for any of
the compilers, or what-have-you?

Some notes & questions:

- I gathered these by the rather error-prone process of copying them
  from the end-user documentation.  If anyone notices anything that's
  missing, or can suggest some way I could discover missing items,
  please do.

- I'm not including any non-standard modules, since maybe those will
  be handled by the packaging system.

- Are the "hood debugging extensions" in NHC and Hugs compatible?
  Should they be included?

- Do any of Hugs, GHC, and NHC disallow Long.Hierarchical.Module.Names
  by default?  Can they all turn them off?

- Should there be a "Force98" option or something which does "-98" in
  NHC, "+98" in Hugs, and forces no other extensions in GHC?
  Presumably, it would disallow other extensions for the other
  compilers as well.

- Does anyone care to provide such a mapping for any other compiler
  flavors?

peace,

  isaac

[2] formerly LIP: http://www.haskell.org/cabal
------------------------------------------------------------
[1]
data Extension = 
	       OverlappingInstances
               | RecursiveDo
               | ParallelListComp
               | MultiParamTypeClasses
               | NoMonomorphismRestriction
               | FunctionalDependencies
               | RankTwoTypes
               | PolymorphicComponents
               | ExistentialQuantification
               | PatternTypeAnnotations
               | ImplicitParams
               | FlexibleContexts
               | FlexibleInstances

	       | TypeSynonymInstances
	       | TemplateHaskell
               | ForeignFunctionInterface
               | AllowOverlappingInstances
               | AllowUndecidableInstances
               | AllowIncoherentInstances
               | InlinePhase
               | ContextStack
               | Arrows
               | Generics
               | NoImplicitPrelude

               | ExtensibleRecords
               | RestrictedTypeSynonyms
               | HereDocuments
               | HoodDebugging
               | UnsafeOverlappingInstances
	       deriving (Show, Read, Eq)

-- |GHC: Return the unsupported extensions, and the flags for the supported extensions
extensionsToGHCFlag :: [ Extension ] -> ([Extension], [Opt])
extensionsToGHCFlag l
    = splitEither $ nub $ map extensionToGHCFlag l
    where
    extensionToGHCFlag :: Extension -> Either Extension String
    extensionToGHCFlag OverlappingInstances         = Right "-fallow-overlapping-instances"
    extensionToGHCFlag TypeSynonymInstances         = Right "-fglasgow-exts"
    extensionToGHCFlag TemplateHaskell              = Right "-fth"
    extensionToGHCFlag ForeignFunctionInterface     = Right "-ffi"
    extensionToGHCFlag NoMonomorphismRestriction    = Right "-fno-monomorphism-restriction"
    extensionToGHCFlag AllowOverlappingInstances    = Right "-fallow-overlapping-instances"
    extensionToGHCFlag AllowUndecidableInstances    = Right "-fallow-undecidable-instances"
    extensionToGHCFlag AllowIncoherentInstances     = Right "-fallow- incoherent-instances"
    extensionToGHCFlag InlinePhase                  = Right "-finline-phase"
    extensionToGHCFlag ContextStack                 = Right "-fcontext-stack"
    extensionToGHCFlag Arrows                       = Right "-farrows"
    extensionToGHCFlag Generics                     = Right "-fgenerics"
    extensionToGHCFlag NoImplicitPrelude            = Right "-fno-implicit-prelude"
    extensionToGHCFlag ImplicitParams               = Right "-fimplicit-params"

    extensionToGHCFlag RecursiveDo                  = Right "-fglasgow-exts"
    extensionToGHCFlag ParallelListComp             = Right "-fglasgow-exts"
    extensionToGHCFlag MultiParamTypeClasses        = Right "-fglasgow-exts"
    extensionToGHCFlag FunctionalDependencies       = Right "-fglasgow-exts"
    extensionToGHCFlag RankTwoTypes                 = Right "-fglasgow-exts"
    extensionToGHCFlag PolymorphicComponents        = Right "-fglasgow-exts"
    extensionToGHCFlag ExistentialQuantification    = Right "-fglasgow-exts"
    extensionToGHCFlag PatternTypeAnnotations       = Right "-fglasgow-exts"
    extensionToGHCFlag FlexibleContexts             = Right "-fglasgow-exts"
    extensionToGHCFlag FlexibleInstances            = Right "-fglasgow-exts"

    extensionToGHCFlag e at ExtensibleRecords          = Left e
    extensionToGHCFlag e at RestrictedTypeSynonyms     = Left e
    extensionToGHCFlag e at HereDocuments              = Left e
    extensionToGHCFlag e at HoodDebugging              = Left e
    extensionToGHCFlag e at UnsafeOverlappingInstances = Left e

-- |NHC: Return the unsupported extensions, and the flags for the supported extensions
extensionsToNHCFlag :: [ Extension ] -> ([Extension], [Opt])
extensionsToNHCFlag l
    = splitEither $ nub $ map extensionToNHCFlag l
      where
      extensionToNHCFlag NoMonomorphismRestriction = Right "" -- not implemented in NHC
      extensionToNHCFlag ForeignFunctionInterface  = Right ""
      extensionToNHCFlag HoodDebugging             = Right ""
      extensionToNHCFlag e                         = Left e

-- |Hugs: Return the unsupported extensions, and the flags for the supported extensions
extensionsToHugsFlag :: [ Extension ] -> ([Extension], [Opt])
extensionsToHugsFlag l
    = splitEither $ nub $ map extensionToHugsFlag l
      where
      extensionToHugsFlag OverlappingInstances       = Right "+o"
      extensionToHugsFlag UnsafeOverlappingInstances = Right "+O"
      extensionToHugsFlag HereDocuments              = Right "+H"
      extensionToHugsFlag RecursiveDo                = Right "-98"
      extensionToHugsFlag ParallelListComp           = Right "-98"
      extensionToHugsFlag MultiParamTypeClasses      = Right "-98"
      extensionToHugsFlag FunctionalDependencies     = Right "-98"
      extensionToHugsFlag RankTwoTypes               = Right "-98"
      extensionToHugsFlag PolymorphicComponents      = Right "-98"
      extensionToHugsFlag ExistentialQuantification  = Right "-98"
      extensionToHugsFlag PatternTypeAnnotations     = Right "-98"
      extensionToHugsFlag ImplicitParams             = Right "-98"
      extensionToHugsFlag ExtensibleRecords          = Right "-98"
      extensionToHugsFlag RestrictedTypeSynonyms     = Right "-98"
      extensionToHugsFlag HoodDebugging              = Right "-98"
      extensionToHugsFlag FlexibleContexts           = Right "-98"
      extensionToHugsFlag FlexibleInstances          = Right "-98"
      extensionToHugsFlag e                          = Left e

splitEither :: [Either a b] -> ([a], [b])
splitEither l = ([a | Left a <- l], [b | Right b <- l])

type Opt = String


More information about the Libraries mailing list