Skip to content
Snippets Groups Projects
Commit 5868a16c authored by Oleg Grenrus's avatar Oleg Grenrus
Browse files

Add IsString instance for ShortText newtypes

parent 47884b36
No related branches found
No related tags found
No related merge requests found
......@@ -40,6 +40,7 @@ module Distribution.Compat.Prelude (
Binary (..),
Alternative (..),
MonadPlus (..),
IsString (..),
-- * Some types
IO, NoCallStackIO,
......@@ -131,6 +132,7 @@ import Data.List (intercalate, intersperse, isPrefixOf,
isSuffixOf, nub, nubBy, sort, sortBy,
unfoldr)
import Data.Maybe
import Data.String (IsString (..))
import Data.Int
import Data.Word
......
......@@ -76,12 +76,12 @@ simple str = ModuleName (stlFromStrings [str])
-- an error if it is used with a string that is not a valid module name. If you
-- are parsing user input then use 'Distribution.Text.simpleParse' instead.
--
fromString :: String -> ModuleName
fromString string = fromComponents (split string)
where
split cs = case break (=='.') cs of
(chunk,[]) -> chunk : []
(chunk,_:rest) -> chunk : split rest
instance IsString ModuleName where
fromString string = fromComponents (split string)
where
split cs = case break (=='.') cs of
(chunk,[]) -> chunk : []
(chunk,_:rest) -> chunk : split rest
-- | Construct a 'ModuleName' from valid module components, i.e. parts
-- separated by dots.
......
......@@ -89,6 +89,12 @@ unPackageName (PackageName s) = fromShortText s
mkPackageName :: String -> PackageName
mkPackageName = PackageName . toShortText
-- | 'mkPackageName'
--
-- @since 2.0
instance IsString PackageName where
fromString = mkPackageName
instance Binary PackageName
instance Text PackageName where
......@@ -123,6 +129,12 @@ unPkgconfigName (PkgconfigName s) = fromShortText s
mkPkgconfigName :: String -> PkgconfigName
mkPkgconfigName = PkgconfigName . toShortText
-- | 'mkPkgconfigName'
--
-- @since 2.0
instance IsString PkgconfigName where
fromString = mkPkgconfigName
instance Binary PkgconfigName
-- pkg-config allows versions and other letters in package names, eg
......@@ -215,6 +227,12 @@ newtype ComponentId = ComponentId ShortText
mkComponentId :: String -> ComponentId
mkComponentId = ComponentId . toShortText
-- | 'mkComponentId'
--
-- @since 2.0
instance IsString ComponentId where
fromString = mkComponentId
-- | Convert 'ComponentId' to 'String'
--
-- @since 2.0
......@@ -288,15 +306,21 @@ instance Text UnitId where
disp = text . unUnitId
parse = mkUnitId <$> Parse.munch1 (\c -> isAlphaNum c || c `elem` "-_.+")
unUnitId :: UnitId -> String
unUnitId (UnitId s) = fromShortText s
-- | If you need backwards compatibility, consider using 'display'
-- instead, which is supported by all versions of Cabal.
--
unUnitId :: UnitId -> String
unUnitId (UnitId s) = fromShortText s
mkUnitId :: String -> UnitId
mkUnitId = UnitId . toShortText
-- | 'mkUnitId'
--
-- @since 2.0
instance IsString UnitId where
fromString = mkUnitId
-- | A 'UnitId' for a definite package. The 'DefUnitId' invariant says
-- that a 'UnitId' identified this way is definite; i.e., it has no
-- unfilled holes.
......@@ -388,6 +412,12 @@ unAbiHash (AbiHash h) = fromShortText h
mkAbiHash :: String -> AbiHash
mkAbiHash = AbiHash . toShortText
-- | 'mkAbiHash'
--
-- @since 2.0
instance IsString AbiHash where
fromString = mkAbiHash
instance Binary AbiHash
instance Text AbiHash where
......
......@@ -102,6 +102,12 @@ newtype FlagName = FlagName ShortText
mkFlagName :: String -> FlagName
mkFlagName = FlagName . toShortText
-- | 'mkFlagName'
--
-- @since 2.0
instance IsString FlagName where
fromString = mkFlagName
-- | Convert 'FlagName' to 'String'
--
-- @since 2.0
......
......@@ -44,6 +44,12 @@ unUnqualComponentName (UnqualComponentName s) = fromShortText s
mkUnqualComponentName :: String -> UnqualComponentName
mkUnqualComponentName = UnqualComponentName . toShortText
-- | 'mkUnqualComponentName'
--
-- @since 2.0
instance IsString UnqualComponentName where
fromString = mkUnqualComponentName
instance Binary UnqualComponentName
instance Text UnqualComponentName where
......
......@@ -17,8 +17,6 @@ import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Utils.String
import Data.String (IsString(..))
#if defined(MIN_VERSION_bytestring)
# if MIN_VERSION_bytestring(0,10,4)
# define HAVE_SHORTBYTESTRING 1
......
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