{-# LANGUAGE TemplateHaskell, DataKinds #-} module System.XDG.FileSystem where import qualified Control.Exception as IO import qualified Data.ByteString.Lazy as BS import Polysemy import Polysemy.Error import qualified System.IO.Error as IO import System.XDG.Error data ReadFile f m a where ReadFile ::FilePath -> ReadFile f m f makeSem ''ReadFile type FileList a = [(FilePath, a)] runReadFileList :: Member (Error XDGError) r => FileList a -> InterpreterFor (ReadFile a) r runReadFileList :: forall (r :: EffectRow) a. Member (Error XDGError) r => FileList a -> InterpreterFor (ReadFile a) r runReadFileList FileList a files = forall (e :: Effect) (r :: EffectRow) a. FirstOrder e "interpret" => (forall (rInitial :: EffectRow) x. e (Sem rInitial) x -> Sem r x) -> Sem (e : r) a -> Sem r a interpret (\(ReadFile FilePath path) -> forall b a. b -> (a -> b) -> Maybe a -> b maybe (forall e (r :: EffectRow) a. Member (Error e) r => e -> Sem r a throw forall a b. (a -> b) -> a -> b $ FilePath -> XDGError FileNotFound FilePath path) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ forall a b. Eq a => a -> [(a, b)] -> Maybe b lookup FilePath path FileList a files ) runReadFileIO :: Members '[Embed IO , Error XDGError] r => InterpreterFor (ReadFile BS.ByteString) r runReadFileIO :: forall (r :: EffectRow). Members '[Embed IO, Error XDGError] r => InterpreterFor (ReadFile ByteString) r runReadFileIO = forall (e :: Effect) (r :: EffectRow) a. FirstOrder e "interpret" => (forall (rInitial :: EffectRow) x. e (Sem rInitial) x -> Sem r x) -> Sem (e : r) a -> Sem r a interpret (\(ReadFile FilePath path) -> do let notFound :: IO.IOException -> Maybe XDGError notFound :: IOException -> Maybe XDGError notFound IOException e = if IOException -> Bool IO.isDoesNotExistError IOException e then forall a. a -> Maybe a Just forall a b. (a -> b) -> a -> b $ FilePath -> XDGError FileNotFound FilePath path else forall a. Maybe a Nothing Either XDGError ByteString result <- forall (m :: * -> *) (r :: EffectRow) a. Member (Embed m) r => m a -> Sem r a embed forall a b. (a -> b) -> a -> b $ forall e b a. Exception e => (e -> Maybe b) -> IO a -> IO (Either b a) IO.tryJust IOException -> Maybe XDGError notFound forall a b. (a -> b) -> a -> b $ FilePath -> IO ByteString BS.readFile FilePath path forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either forall e (r :: EffectRow) a. Member (Error e) r => e -> Sem r a throw forall (f :: * -> *) a. Applicative f => a -> f a pure Either XDGError ByteString result )