{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TemplateHaskell #-}
module Path.Internal
( Path(..)
, hasParentDir
, relRootFP
, toFilePath
)
where
import Control.DeepSeq (NFData (..))
import Data.Aeson (ToJSON (..), ToJSONKey(..))
import Data.Aeson.Types (toJSONKeyText)
import qualified Data.Text as T (pack)
import GHC.Generics (Generic)
import Data.Data
import Data.Hashable
import qualified Data.List as L
import qualified Language.Haskell.TH.Syntax as TH
import qualified System.FilePath as FilePath
newtype Path b t = Path FilePath
deriving (Data, Typeable, Generic)
instance Eq (Path b t) where
(==) (Path x) (Path y) = x == y
instance Ord (Path b t) where
compare (Path x) (Path y) = compare x y
relRootFP :: FilePath
relRootFP = '.' : [FilePath.pathSeparator]
toFilePath :: Path b t -> FilePath
toFilePath (Path []) = relRootFP
toFilePath (Path x) = x
instance Show (Path b t) where
show = show . toFilePath
instance NFData (Path b t) where
rnf (Path x) = rnf x
instance ToJSON (Path b t) where
toJSON = toJSON . toFilePath
{-# INLINE toJSON #-}
#if MIN_VERSION_aeson(0,10,0)
toEncoding = toEncoding . toFilePath
{-# INLINE toEncoding #-}
#endif
instance ToJSONKey (Path b t) where
toJSONKey = toJSONKeyText $ T.pack . toFilePath
instance Hashable (Path b t) where
hashWithSalt n path = hashWithSalt n (toFilePath path)
hasParentDir :: FilePath -> Bool
hasParentDir filepath' =
(filepath' == "..") ||
("/.." `L.isSuffixOf` filepath) ||
("/../" `L.isInfixOf` filepath) ||
("../" `L.isPrefixOf` filepath)
where
filepath =
case FilePath.pathSeparator of
'/' -> filepath'
x -> map (\y -> if x == y then '/' else y) filepath'
instance (Typeable a, Typeable b) => TH.Lift (Path a b) where
lift p@(Path str) = do
let btc = typeRepTyCon $ typeRep $ mkBaseProxy p
ttc = typeRepTyCon $ typeRep $ mkTypeProxy p
bn <- lookupTypeNameThrow $ tyConName btc
tn <- lookupTypeNameThrow $ tyConName ttc
[|Path $(return (TH.LitE (TH.StringL str))) :: Path
$(return $ TH.ConT bn)
$(return $ TH.ConT tn)
|]
where
mkBaseProxy :: Path a b -> Proxy a
mkBaseProxy _ = Proxy
mkTypeProxy :: Path a b -> Proxy b
mkTypeProxy _ = Proxy
lookupTypeNameThrow n = TH.lookupTypeName n
>>= maybe (fail $ "Not in scope: type constructor ‘" ++ n ++ "’") return
#if MIN_VERSION_template_haskell(2,16,0)
liftTyped = TH.unsafeTExpCoerce . TH.lift
#endif