Version number or non-alphanumeric character in package name [GHC-21926]
Language extension: PackageImports
Version number or non-alphanumeric character in the package. Each of dash-separated components of package name must consist of alphanumeric characters (as defined by Data.Char.isAlphaNum
), at least one of which is not a digit.
Note that you will also see this error if the package name consists only of digits.
The package name in this case refers to the one mentioned in an import when using the PackageImports
language extension.
Examples
Non-alphanumeric characters in the package name
Non-alphanumeric-in-package.hs
Before
{-# LANGUAGE PackageImports #-}
module NonAlphanumericCharacterNameInPackage where
import "&*$^%!@()" Package.With.Non.Alphanumeric.Characters
After
{-# LANGUAGE PackageImports #-}
module NonAlphanumericCharacterNameInPackage where
import "some-existing-package" Package.With.Non.Alphanumeric.Characters
Version number in package name
Version-name-in-package.hs
Before
{-# LANGUAGE PackageImports #-}
module VersionNameInPackage where
import "some-package-0.1.2.3" Package.With.Version
After
{-# LANGUAGE PackageImports #-}
module VersionNameInPackage where
import "some-package" Package.With.Version