{-# LANGUAGE GeneralizedNewtypeDeriving, FlexibleInstances #-}moduleDevelopment.Shake.Internal.FileName(FileName ,fileNameFromString ,fileNameFromByteString ,fileNameToString ,fileNameToByteString ,filepathNormalise )whereimportqualifiedData.ByteString.Char8asBSimportqualifiedData.ByteString.UTF8asUTF8importDevelopment.Shake.Classes importqualifiedSystem.FilePathasNativeimportGeneral.Binary importSystem.Info.ExtraimportData.List----------------------------------------------------------------------- FileName newtype-- | UTF8 ByteStringnewtypeFileName =FileName BS.ByteStringderiving(Eq FileName Eq FileName => (Int -> FileName -> Int) -> (FileName -> Int) -> Hashable FileName Int -> FileName -> Int FileName -> Int forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a $chashWithSalt :: Int -> FileName -> Int hashWithSalt :: Int -> FileName -> Int $chash :: FileName -> Int hash :: FileName -> Int Hashable,Get FileName [FileName] -> Put FileName -> Put (FileName -> Put) -> Get FileName -> ([FileName] -> Put) -> Binary FileName forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t $cput :: FileName -> Put put :: FileName -> Put $cget :: Get FileName get :: Get FileName $cputList :: [FileName] -> Put putList :: [FileName] -> Put Binary,ByteString -> FileName FileName -> Builder (FileName -> Builder) -> (ByteString -> FileName) -> BinaryEx FileName forall a. (a -> Builder) -> (ByteString -> a) -> BinaryEx a $cputEx :: FileName -> Builder putEx :: FileName -> Builder $cgetEx :: ByteString -> FileName getEx :: ByteString -> FileName BinaryEx ,FileName -> FileName -> Bool (FileName -> FileName -> Bool) -> (FileName -> FileName -> Bool) -> Eq FileName forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: FileName -> FileName -> Bool == :: FileName -> FileName -> Bool $c/= :: FileName -> FileName -> Bool /= :: FileName -> FileName -> Bool Eq,FileName -> () (FileName -> ()) -> NFData FileName forall a. (a -> ()) -> NFData a $crnf :: FileName -> () rnf :: FileName -> () NFData)instanceShowFileName whereshow :: FileName -> String show =FileName -> String fileNameToString instanceBinaryEx [FileName ]whereputEx :: [FileName] -> Builder putEx =[ByteString] -> Builder forall a. BinaryEx a => a -> Builder putEx ([ByteString] -> Builder) -> ([FileName] -> [ByteString]) -> [FileName] -> Builder forall b c a. (b -> c) -> (a -> b) -> a -> c .(FileName -> ByteString) -> [FileName] -> [ByteString] forall a b. (a -> b) -> [a] -> [b] map(\(FileName ByteString x )->ByteString x )getEx :: ByteString -> [FileName] getEx =(ByteString -> FileName) -> [ByteString] -> [FileName] forall a b. (a -> b) -> [a] -> [b] mapByteString -> FileName FileName ([ByteString] -> [FileName]) -> (ByteString -> [ByteString]) -> ByteString -> [FileName] forall b c a. (b -> c) -> (a -> b) -> a -> c .ByteString -> [ByteString] forall a. BinaryEx a => ByteString -> a getEx fileNameToString ::FileName ->FilePathfileNameToString :: FileName -> String fileNameToString =ByteString -> String UTF8.toString(ByteString -> String) -> (FileName -> ByteString) -> FileName -> String forall b c a. (b -> c) -> (a -> b) -> a -> c .FileName -> ByteString fileNameToByteString fileNameToByteString ::FileName ->BS.ByteStringfileNameToByteString :: FileName -> ByteString fileNameToByteString (FileName ByteString x )=ByteString x fileNameFromString ::FilePath->FileName fileNameFromString :: String -> FileName fileNameFromString =ByteString -> FileName fileNameFromByteString (ByteString -> FileName) -> (String -> ByteString) -> String -> FileName forall b c a. (b -> c) -> (a -> b) -> a -> c .String -> ByteString UTF8.fromStringfileNameFromByteString ::BS.ByteString->FileName fileNameFromByteString :: ByteString -> FileName fileNameFromByteString =ByteString -> FileName FileName (ByteString -> FileName) -> (ByteString -> ByteString) -> ByteString -> FileName forall b c a. (b -> c) -> (a -> b) -> a -> c .ByteString -> ByteString filepathNormalise ----------------------------------------------------------------------- NORMALISATION-- | Equivalent to @toStandard . normaliseEx@ from "Development.Shake.FilePath".filepathNormalise ::BS.ByteString->BS.ByteStringfilepathNormalise :: ByteString -> ByteString filepathNormalise ByteString xs |Bool isWindows,Just(Char a ,ByteString xs )<-ByteString -> Maybe (Char, ByteString) BS.unconsByteString xs ,Char -> Bool sep Char a ,Just(Char b ,ByteString _)<-ByteString -> Maybe (Char, ByteString) BS.unconsByteString xs ,Char -> Bool sep Char b =Char '/'Char -> ByteString -> ByteString `BS.cons`ByteString -> ByteString f ByteString xs |Bool otherwise=ByteString -> ByteString f ByteString xs wheresep :: Char -> Bool sep =Char -> Bool Native.isPathSeparatorf :: ByteString -> ByteString f ByteString o =ByteString -> ByteString -> ByteString deslash ByteString o (ByteString -> ByteString) -> ByteString -> ByteString forall a b. (a -> b) -> a -> b $[ByteString] -> ByteString BS.concat([ByteString] -> ByteString) -> [ByteString] -> ByteString forall a b. (a -> b) -> a -> b $(ByteString slash ByteString -> [ByteString] -> [ByteString] forall a. a -> [a] -> [a] :)([ByteString] -> [ByteString]) -> [ByteString] -> [ByteString] forall a b. (a -> b) -> a -> b $ByteString -> [ByteString] -> [ByteString] forall a. a -> [a] -> [a] intersperseByteString slash ([ByteString] -> [ByteString]) -> [ByteString] -> [ByteString] forall a b. (a -> b) -> a -> b $[ByteString] -> [ByteString] forall a. [a] -> [a] reverse([ByteString] -> [ByteString]) -> [ByteString] -> [ByteString] forall a b. (a -> b) -> a -> b $(ByteString BS.emptyByteString -> [ByteString] -> [ByteString] forall a. a -> [a] -> [a] :)([ByteString] -> [ByteString]) -> [ByteString] -> [ByteString] forall a b. (a -> b) -> a -> b $Int -> [ByteString] -> [ByteString] g Int 0([ByteString] -> [ByteString]) -> [ByteString] -> [ByteString] forall a b. (a -> b) -> a -> b $[ByteString] -> [ByteString] forall a. [a] -> [a] reverse([ByteString] -> [ByteString]) -> [ByteString] -> [ByteString] forall a b. (a -> b) -> a -> b $ByteString -> [ByteString] split ByteString o deslash :: ByteString -> ByteString -> ByteString deslash ByteString o ByteString x |ByteString x ByteString -> ByteString -> Bool forall a. Eq a => a -> a -> Bool ==ByteString slash =case(Bool pre ,Bool pos )of(Bool True,Bool True)->ByteString slash (Bool True,Bool False)->String -> ByteString BS.packString "/."(Bool False,Bool True)->String -> ByteString BS.packString "./"(Bool False,Bool False)->ByteString dot |Bool otherwise=(ifBool pre thenByteString -> ByteString forall a. a -> a idelseHasCallStack => ByteString -> ByteString ByteString -> ByteString BS.tail)(ByteString -> ByteString) -> ByteString -> ByteString forall a b. (a -> b) -> a -> b $(ifBool pos thenByteString -> ByteString forall a. a -> a idelseHasCallStack => ByteString -> ByteString ByteString -> ByteString BS.init)ByteString x wherepre :: Bool pre =Bool -> Bool not(ByteString -> Bool BS.nullByteString o )Bool -> Bool -> Bool &&Char -> Bool sep (ByteString -> Char BS.headByteString o )pos :: Bool pos =Bool -> Bool not(ByteString -> Bool BS.nullByteString o )Bool -> Bool -> Bool &&Char -> Bool sep (ByteString -> Char BS.lastByteString o )g :: Int -> [ByteString] -> [ByteString] g Int i []=Int -> ByteString -> [ByteString] forall a. Int -> a -> [a] replicateInt i ByteString dotDot g Int i (ByteString x :[ByteString] xs )|ByteString -> Bool BS.nullByteString x =Int -> [ByteString] -> [ByteString] g Int i [ByteString] xs g Int i (ByteString x :[ByteString] xs )|ByteString x ByteString -> ByteString -> Bool forall a. Eq a => a -> a -> Bool ==ByteString dotDot =Int -> [ByteString] -> [ByteString] g (Int i Int -> Int -> Int forall a. Num a => a -> a -> a +Int 1)[ByteString] xs g Int i (ByteString x :[ByteString] xs )|ByteString x ByteString -> ByteString -> Bool forall a. Eq a => a -> a -> Bool ==ByteString dot =Int -> [ByteString] -> [ByteString] g Int i [ByteString] xs g Int 0(ByteString x :[ByteString] xs )=ByteString x ByteString -> [ByteString] -> [ByteString] forall a. a -> [a] -> [a] :Int -> [ByteString] -> [ByteString] g Int 0[ByteString] xs g Int i (ByteString _:[ByteString] xs )=Int -> [ByteString] -> [ByteString] g (Int i Int -> Int -> Int forall a. Num a => a -> a -> a -Int 1)[ByteString] xs -- equivalent to eliminating ../xsplit :: ByteString -> [ByteString] split =(Char -> Bool) -> ByteString -> [ByteString] BS.splitWithChar -> Bool sep dotDot :: ByteString dotDot =String -> ByteString BS.packString ".."dot :: ByteString dot =Char -> ByteString BS.singletonChar '.'slash :: ByteString slash =Char -> ByteString BS.singletonChar '/'