{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.Backpack.Id
  ( computeComponentId
  , computeCompatPackageKey
  ) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.PackageDescription
import Distribution.Simple.Compiler
import Distribution.Simple.Flag (Flag (..))
import qualified Distribution.Simple.InstallDirs as InstallDirs
import Distribution.Simple.LocalBuildInfo
import Distribution.Types.ComponentId
import Distribution.Types.MungedPackageName
import Distribution.Types.UnitId
import Distribution.Utils.Base62
import Distribution.Version
import Distribution.Parsec (simpleParsec)
import Distribution.Pretty
  ( prettyShow
  )
computeComponentId
  :: Bool 
  -> Flag String
  -> Flag ComponentId
  -> PackageIdentifier
  -> ComponentName
  
  -> Maybe ([ComponentId], FlagAssignment)
  -> ComponentId
computeComponentId :: Bool
-> Flag String
-> Flag ComponentId
-> PackageIdentifier
-> ComponentName
-> Maybe ([ComponentId], FlagAssignment)
-> ComponentId
computeComponentId Bool
deterministic Flag String
mb_ipid Flag ComponentId
mb_cid PackageIdentifier
pid ComponentName
cname Maybe ([ComponentId], FlagAssignment)
mb_details =
  
  
  
  
  let hash_suffix :: String
hash_suffix
        | Just ([ComponentId]
dep_ipids, FlagAssignment
flags) <- Maybe ([ComponentId], FlagAssignment)
mb_details =
            String
"-"
              String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
hashToBase62
                
                
                
                ( PackageIdentifier -> String
forall a. Pretty a => a -> String
prettyShow PackageIdentifier
pid
                    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [ComponentId] -> String
forall a. Show a => a -> String
show [ComponentId]
dep_ipids
                    String -> String -> String
forall a. [a] -> [a] -> [a]
++ FlagAssignment -> String
forall a. Show a => a -> String
show FlagAssignment
flags
                )
        | Bool
otherwise = String
""
      generated_base :: String
generated_base = PackageIdentifier -> String
forall a. Pretty a => a -> String
prettyShow PackageIdentifier
pid String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
hash_suffix
      explicit_base :: String -> String
explicit_base String
cid0 =
        PathTemplate -> String
fromPathTemplate
          ( PathTemplateEnv -> PathTemplate -> PathTemplate
InstallDirs.substPathTemplate
              PathTemplateEnv
env
              (String -> PathTemplate
toPathTemplate String
cid0)
          )
        where
          
          
          env :: PathTemplateEnv
env = PackageIdentifier -> UnitId -> PathTemplateEnv
packageTemplateEnv PackageIdentifier
pid (String -> UnitId
mkUnitId String
"")
      actual_base :: String
actual_base = case Flag String
mb_ipid of
        Flag String
ipid0 -> String -> String
explicit_base String
ipid0
        Flag String
NoFlag
          | Bool
deterministic -> PackageIdentifier -> String
forall a. Pretty a => a -> String
prettyShow PackageIdentifier
pid
          | Bool
otherwise -> String
generated_base
   in case Flag ComponentId
mb_cid of
        Flag ComponentId
cid -> ComponentId
cid
        Flag ComponentId
NoFlag ->
          String -> ComponentId
mkComponentId (String -> ComponentId) -> String -> ComponentId
forall a b. (a -> b) -> a -> b
$
            String
actual_base
              String -> String -> String
forall a. [a] -> [a] -> [a]
++ ( case ComponentName -> Maybe UnqualComponentName
componentNameString ComponentName
cname of
                    Maybe UnqualComponentName
Nothing -> String
""
                    Just UnqualComponentName
s -> String
"-" String -> String -> String
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> String
unUnqualComponentName UnqualComponentName
s
                 )
computeCompatPackageKey
  :: Compiler
  -> MungedPackageName
  -> Version
  -> UnitId
  -> String
computeCompatPackageKey :: Compiler -> MungedPackageName -> Version -> UnitId -> String
computeCompatPackageKey Compiler
comp MungedPackageName
pkg_name Version
pkg_version UnitId
uid
  | Bool -> Bool
not (Compiler -> Bool
packageKeySupported Compiler
comp Bool -> Bool -> Bool
|| Compiler -> Bool
unitIdSupported Compiler
comp) =
      MungedPackageName -> String
forall a. Pretty a => a -> String
prettyShow MungedPackageName
pkg_name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"-" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Version -> String
forall a. Pretty a => a -> String
prettyShow Version
pkg_version
  | Bool -> Bool
not (Compiler -> Bool
unifiedIPIDRequired Compiler
comp) =
      let str :: String
str = UnitId -> String
unUnitId UnitId
uid 
          mb_verbatim_key :: Maybe String
mb_verbatim_key =
            case String -> Maybe PackageIdentifier
forall a. Parsec a => String -> Maybe a
simpleParsec String
str :: Maybe PackageId of
              
              
              
              Just PackageIdentifier
pid0 | PackageIdentifier -> String
forall a. Pretty a => a -> String
prettyShow PackageIdentifier
pid0 String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
str -> String -> Maybe String
forall a. a -> Maybe a
Just String
str
              Maybe PackageIdentifier
_ -> Maybe String
forall a. Maybe a
Nothing
          mb_truncated_key :: Maybe String
mb_truncated_key =
            let cand :: String
cand = String -> String
forall a. [a] -> [a]
reverse ((Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
takeWhile Char -> Bool
isAlphaNum (String -> String
forall a. [a] -> [a]
reverse String
str))
             in if String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
cand Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
22 Bool -> Bool -> Bool
&& (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isAlphaNum String
cand
                  then String -> Maybe String
forall a. a -> Maybe a
Just String
cand
                  else Maybe String
forall a. Maybe a
Nothing
          rehashed_key :: String
rehashed_key = String -> String
hashToBase62 String
str
       in String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
rehashed_key (Maybe String
mb_verbatim_key Maybe String -> Maybe String -> Maybe String
forall a. Maybe a -> Maybe a -> Maybe a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` Maybe String
mb_truncated_key)
  | Bool
otherwise = UnitId -> String
forall a. Pretty a => a -> String
prettyShow UnitId
uid