hnix/src/Nix/NixString.hs

71 lines
2.2 KiB
Haskell
Raw Normal View History

2018-05-13 20:13:30 +02:00
{-# LANGUAGE DeriveGeneric #-}
module Nix.NixString (
NixString
, stringHasContext
, hackyStringIgnoreContextMaybe
, hackyStringIgnoreContext
, hackyMakeNixStringWithoutContext
, hackyModifyNixContents
2018-05-13 20:13:30 +02:00
) where
import qualified Data.HashSet as S
import Data.Hashable
import Data.Text (Text)
import GHC.Generics
import Data.Semigroup
{-# WARNING hackyStringIgnoreContextMaybe, hackyStringIgnoreContext, hackyMakeNixStringWithoutContext, hackyModifyNixContents "This NixString function needs to be replaced" #-}
2018-05-13 20:13:30 +02:00
-- | A 'ContextFlavor' describes the sum of possible derivations for string contexts
data ContextFlavor =
DirectPath
| DerivationOutput !Text
deriving (Show, Eq, Ord, Generic)
instance Hashable ContextFlavor
-- | A 'StringContext' ...
data StringContext =
StringContext { scPath :: !Text
, scFlavor :: !ContextFlavor
} deriving (Eq, Ord, Show, Generic)
instance Hashable StringContext
data NixString = NixString
{ nsContents :: !Text
, nsContext :: !(S.HashSet StringContext)
} deriving (Eq, Ord, Show, Generic)
instance Hashable NixString
instance Semigroup NixString where
NixString s1 t1 <> NixString s2 t2 = NixString (s1 <> s2) (t1 <> t2)
instance Monoid NixString where
mempty = NixString mempty mempty
mappend = (<>)
-- | Extract the string contents from a NixString that has no context
hackyStringIgnoreContextMaybe :: NixString -> Maybe Text
hackyStringIgnoreContextMaybe (NixString s c) | null c = Just s
2018-05-13 20:13:30 +02:00
| otherwise = Nothing
-- | Extract the string contents from a NixString even if the NixString has an associated context
hackyStringIgnoreContext :: NixString -> Text
hackyStringIgnoreContext (NixString s _) = s
2018-05-13 20:13:30 +02:00
-- | Returns True if the NixString has an associated context
stringHasContext :: NixString -> Bool
stringHasContext (NixString _ c) = not (null c)
2018-05-13 20:13:30 +02:00
-- | Constructs a NixString without a context
hackyMakeNixStringWithoutContext :: Text -> NixString
hackyMakeNixStringWithoutContext = flip NixString mempty
2018-05-13 20:13:30 +02:00
-- | Modify the string part of the NixString -- ignores the context
hackyModifyNixContents :: (Text -> Text) -> NixString -> NixString
hackyModifyNixContents f (NixString s c) = NixString (f s) c
2018-05-13 20:13:30 +02:00