{-# LANGUAGE OverloadedStrings #-} module Distribution.Nixpkgs.Haskell.FromCabal.Normalize ( normalize ) where import Control.Lens import qualified Data.Set as Set import Data.String import Distribution.Nixpkgs.Haskell import Distribution.Nixpkgs.Haskell.FromCabal.Name (toNixName) import Distribution.Nixpkgs.Meta import Distribution.Package import Language.Nix hiding ( quote ) normalize :: Derivation -> Derivation normalize :: Derivation -> Derivation normalize Derivation drv = Derivation drv Derivation -> (Derivation -> Derivation) -> Derivation forall a b. a -> (a -> b) -> b & ASetter Derivation Derivation BuildInfo BuildInfo -> (BuildInfo -> BuildInfo) -> Derivation -> Derivation forall s t a b. ASetter s t a b -> (a -> b) -> s -> t over ASetter Derivation Derivation BuildInfo BuildInfo Lens' Derivation BuildInfo libraryDepends (PackageName -> BuildInfo -> BuildInfo normalizeBuildInfo (Derivation -> PackageName forall pkg. Package pkg => pkg -> PackageName packageName Derivation drv)) Derivation -> (Derivation -> Derivation) -> Derivation forall a b. a -> (a -> b) -> b & ASetter Derivation Derivation BuildInfo BuildInfo -> (BuildInfo -> BuildInfo) -> Derivation -> Derivation forall s t a b. ASetter s t a b -> (a -> b) -> s -> t over ASetter Derivation Derivation BuildInfo BuildInfo Lens' Derivation BuildInfo executableDepends (PackageName -> BuildInfo -> BuildInfo normalizeBuildInfo (Derivation -> PackageName forall pkg. Package pkg => pkg -> PackageName packageName Derivation drv)) Derivation -> (Derivation -> Derivation) -> Derivation forall a b. a -> (a -> b) -> b & ASetter Derivation Derivation BuildInfo BuildInfo -> (BuildInfo -> BuildInfo) -> Derivation -> Derivation forall s t a b. ASetter s t a b -> (a -> b) -> s -> t over ASetter Derivation Derivation BuildInfo BuildInfo Lens' Derivation BuildInfo testDepends (PackageName -> BuildInfo -> BuildInfo normalizeBuildInfo (Derivation -> PackageName forall pkg. Package pkg => pkg -> PackageName packageName Derivation drv)) Derivation -> (Derivation -> Derivation) -> Derivation forall a b. a -> (a -> b) -> b & ASetter Derivation Derivation BuildInfo BuildInfo -> (BuildInfo -> BuildInfo) -> Derivation -> Derivation forall s t a b. ASetter s t a b -> (a -> b) -> s -> t over ASetter Derivation Derivation BuildInfo BuildInfo Lens' Derivation BuildInfo benchmarkDepends (PackageName -> BuildInfo -> BuildInfo normalizeBuildInfo (Derivation -> PackageName forall pkg. Package pkg => pkg -> PackageName packageName Derivation drv)) Derivation -> (Derivation -> Derivation) -> Derivation forall a b. a -> (a -> b) -> b & ASetter Derivation Derivation Meta Meta -> (Meta -> Meta) -> Derivation -> Derivation forall s t a b. ASetter s t a b -> (a -> b) -> s -> t over ASetter Derivation Derivation Meta Meta Lens' Derivation Meta metaSection Meta -> Meta normalizeMeta Derivation -> (Derivation -> Derivation) -> Derivation forall a b. a -> (a -> b) -> b & (Bool -> Identity Bool) -> Derivation -> Identity Derivation Lens' Derivation Bool jailbreak ((Bool -> Identity Bool) -> Derivation -> Identity Derivation) -> (Bool -> Bool) -> Derivation -> Derivation forall s t a b. ASetter s t a b -> (a -> b) -> s -> t %~ (Bool -> Bool -> Bool && (Derivation -> PackageName forall pkg. Package pkg => pkg -> PackageName packageName Derivation drv PackageName -> PackageName -> Bool forall a. Eq a => a -> a -> Bool /= PackageName "jailbreak-cabal")) normalizeBuildInfo :: PackageName -> BuildInfo -> BuildInfo normalizeBuildInfo :: PackageName -> BuildInfo -> BuildInfo normalizeBuildInfo PackageName pname BuildInfo bi = BuildInfo bi BuildInfo -> (BuildInfo -> BuildInfo) -> BuildInfo forall a b. a -> (a -> b) -> b & (Set Binding -> Identity (Set Binding)) -> BuildInfo -> Identity BuildInfo Lens' BuildInfo (Set Binding) haskell ((Set Binding -> Identity (Set Binding)) -> BuildInfo -> Identity BuildInfo) -> (Set Binding -> Set Binding) -> BuildInfo -> BuildInfo forall s t a b. ASetter s t a b -> (a -> b) -> s -> t %~ (Binding -> Bool) -> Set Binding -> Set Binding forall a. (a -> Bool) -> Set a -> Set a Set.filter (\Binding b -> Getting Identifier Binding Identifier -> Binding -> Identifier forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a view Getting Identifier Binding Identifier Lens' Binding Identifier localName Binding b Identifier -> Identifier -> Bool forall a. Eq a => a -> a -> Bool /= PackageName -> Identifier toNixName PackageName pname) BuildInfo -> (BuildInfo -> BuildInfo) -> BuildInfo forall a b. a -> (a -> b) -> b & (Set Binding -> Identity (Set Binding)) -> BuildInfo -> Identity BuildInfo Lens' BuildInfo (Set Binding) tool ((Set Binding -> Identity (Set Binding)) -> BuildInfo -> Identity BuildInfo) -> (Set Binding -> Set Binding) -> BuildInfo -> BuildInfo forall s t a b. ASetter s t a b -> (a -> b) -> s -> t %~ (Binding -> Bool) -> Set Binding -> Set Binding forall a. (a -> Bool) -> Set a -> Set a Set.filter (\Binding b -> Getting Identifier Binding Identifier -> Binding -> Identifier forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a view Getting Identifier Binding Identifier Lens' Binding Identifier localName Binding b Identifier -> Identifier -> Bool forall a. Eq a => a -> a -> Bool /= PackageName -> Identifier toNixName PackageName pname) normalizeMeta :: Meta -> Meta normalizeMeta :: Meta -> Meta normalizeMeta Meta meta = Meta meta Meta -> (Meta -> Meta) -> Meta forall a b. a -> (a -> b) -> b & (String -> Identity String) -> Meta -> Identity Meta Lens' Meta String description ((String -> Identity String) -> Meta -> Identity Meta) -> (String -> String) -> Meta -> Meta forall s t a b. ASetter s t a b -> (a -> b) -> s -> t %~ String -> String normalizeSynopsis Meta -> (Meta -> Meta) -> Meta forall a b. a -> (a -> b) -> b & (Maybe (Set NixpkgsPlatform) -> Identity (Maybe (Set NixpkgsPlatform))) -> Meta -> Identity Meta Lens' Meta (Maybe (Set NixpkgsPlatform)) hydraPlatforms ((Maybe (Set NixpkgsPlatform) -> Identity (Maybe (Set NixpkgsPlatform))) -> Meta -> Identity Meta) -> (Maybe (Set NixpkgsPlatform) -> Maybe (Set NixpkgsPlatform)) -> Meta -> Meta forall s t a b. ASetter s t a b -> (a -> b) -> s -> t %~ (if Meta metaMeta -> Getting Bool Meta Bool -> Bool forall s a. s -> Getting a s a -> a ^.Getting Bool Meta Bool Lens' Meta Bool broken then Maybe (Set NixpkgsPlatform) -> Maybe (Set NixpkgsPlatform) -> Maybe (Set NixpkgsPlatform) forall a b. a -> b -> a const (Set NixpkgsPlatform -> Maybe (Set NixpkgsPlatform) forall a. a -> Maybe a Just Set NixpkgsPlatform forall a. Set a Set.empty) else Maybe (Set NixpkgsPlatform) -> Maybe (Set NixpkgsPlatform) forall a. a -> a id) normalizeSynopsis :: String -> String normalizeSynopsis :: String -> String normalizeSynopsis String desc | String -> Bool forall a. [a] -> Bool forall (t :: * -> *) a. Foldable t => t a -> Bool null String desc = [] | String -> Char forall a. HasCallStack => [a] -> a last String desc Char -> Char -> Bool forall a. Eq a => a -> a -> Bool == Char '.' Bool -> Bool -> Bool && String -> Int forall a. [a] -> Int forall (t :: * -> *) a. Foldable t => t a -> Int length ((Char -> Bool) -> String -> String forall a. (a -> Bool) -> [a] -> [a] filter (Char '.'Char -> Char -> Bool forall a. Eq a => a -> a -> Bool ==) String desc) Int -> Int -> Bool forall a. Eq a => a -> a -> Bool == Int 1 = String -> String normalizeSynopsis (String -> String forall a. HasCallStack => [a] -> [a] init String desc) | Bool otherwise = String -> String quote ([String] -> String unwords (String -> [String] words String desc)) quote :: String -> String quote :: String -> String quote (Char '\\':Char c:String cs) = Char '\\' Char -> String -> String forall a. a -> [a] -> [a] : Char c Char -> String -> String forall a. a -> [a] -> [a] : String -> String quote String cs quote (Char '"':String cs) = Char '\\' Char -> String -> String forall a. a -> [a] -> [a] : Char '"' Char -> String -> String forall a. a -> [a] -> [a] : String -> String quote String cs quote (Char c:String cs) = Char c Char -> String -> String forall a. a -> [a] -> [a] : String -> String quote String cs quote [] = []