module Distribution.Types.ComponentId
( ComponentId, unComponentId, mkComponentId
) where
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Utils.ShortText
import Distribution.Pretty
import Distribution.Parsec
import qualified Distribution.Compat.CharParsing as P
import Text.PrettyPrint (text)
newtype ComponentId = ComponentId ShortText
deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
mkComponentId :: String -> ComponentId
mkComponentId = ComponentId . toShortText
unComponentId :: ComponentId -> String
unComponentId (ComponentId s) = fromShortText s
instance IsString ComponentId where
fromString = mkComponentId
instance Binary ComponentId
instance Structured ComponentId
instance Pretty ComponentId where
pretty = text . unComponentId
instance Parsec ComponentId where
parsec = mkComponentId `fmap` P.munch1 abi_char
where abi_char c = isAlphaNum c || c `elem` "-_."
instance NFData ComponentId where
rnf = rnf . unComponentId