Skip to content
Snippets Groups Projects
Unverified Commit 6a7656ef authored by Phil de Joux's avatar Phil de Joux
Browse files

Use knownLanguages for describing Language

parent 12223d7b
No related branches found
No related tags found
No related merge requests found
...@@ -39,8 +39,10 @@ module Distribution.Described ( ...@@ -39,8 +39,10 @@ module Distribution.Described (
) where ) where
import Prelude import Prelude
(Bool (..), Char, Either (..), Enum (..), Eq (..), Ord (..), Show (..), String, elem, fmap, foldr, id, map, maybe, otherwise, return, undefined, ($), ( Bool (..), Char, Either (..), Enum (..), Eq (..), Ord (..), Show (..), String
(.)) , elem, fmap, foldr, id, map, maybe, otherwise, return, reverse, undefined
, ($), (.), (<$>)
)
import Data.Functor.Identity (Identity (..)) import Data.Functor.Identity (Identity (..))
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
...@@ -100,7 +102,7 @@ import Distribution.Types.UnqualComponentName (UnqualComponentName) ...@@ -100,7 +102,7 @@ import Distribution.Types.UnqualComponentName (UnqualComponentName)
import Distribution.Utils.Path (LicenseFile, PackageDir, SourceDir, SymbolicPath) import Distribution.Utils.Path (LicenseFile, PackageDir, SourceDir, SymbolicPath)
import Distribution.Verbosity (Verbosity) import Distribution.Verbosity (Verbosity)
import Distribution.Version (Version, VersionRange) import Distribution.Version (Version, VersionRange)
import Language.Haskell.Extension (Extension, Language) import Language.Haskell.Extension (Extension, Language, knownLanguages)
-- | Class describing the pretty/parsec format of a. -- | Class describing the pretty/parsec format of a.
class (Pretty a, Parsec a) => Described a where class (Pretty a, Parsec a) => Described a where
...@@ -422,7 +424,7 @@ instance Described IncludeRenaming where ...@@ -422,7 +424,7 @@ instance Described IncludeRenaming where
mr = describe (Proxy :: Proxy ModuleRenaming) mr = describe (Proxy :: Proxy ModuleRenaming)
instance Described Language where instance Described Language where
describe _ = REUnion ["GHC2021", "Haskell2010", "Haskell98"] describe _ = REUnion $ (REString . show) <$> reverse knownLanguages
instance Described LegacyExeDependency where instance Described LegacyExeDependency where
describe _ = RETodo describe _ = RETodo
......
...@@ -63,7 +63,7 @@ instance Structured Language ...@@ -63,7 +63,7 @@ instance Structured Language
instance NFData Language where rnf = genericRnf instance NFData Language where rnf = genericRnf
-- | List of known (supported) languages for GHC -- | List of known (supported) languages for GHC, oldest first.
knownLanguages :: [Language] knownLanguages :: [Language]
knownLanguages = [Haskell98, Haskell2010, GHC2021] knownLanguages = [Haskell98, Haskell2010, GHC2021]
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment