{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE TemplateHaskell #-} module Horizon.Spec.Types.OverlayFile (OverlayFile(MkOverlayFile), fromOverlayFile, mkOverlayFile) where import Data.Kind (Type) import Dhall (FromDhall, ToDhall) import Language.Haskell.TH (Exp, Q) import Language.Haskell.TH.Lift (deriveLift, lift) import Path (File, Path, Rel, parseRelFile) import Path.Dhall () type OverlayFile :: Type newtype OverlayFile = MkOverlayFile { OverlayFile -> Path Rel File fromOverlayFile :: Path Rel File } deriving stock (OverlayFile -> OverlayFile -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: OverlayFile -> OverlayFile -> Bool $c/= :: OverlayFile -> OverlayFile -> Bool == :: OverlayFile -> OverlayFile -> Bool $c== :: OverlayFile -> OverlayFile -> Bool Eq, Int -> OverlayFile -> ShowS [OverlayFile] -> ShowS OverlayFile -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [OverlayFile] -> ShowS $cshowList :: [OverlayFile] -> ShowS show :: OverlayFile -> String $cshow :: OverlayFile -> String showsPrec :: Int -> OverlayFile -> ShowS $cshowsPrec :: Int -> OverlayFile -> ShowS Show) deriving newtype (InputNormalizer -> Decoder OverlayFile forall a. (InputNormalizer -> Decoder a) -> FromDhall a autoWith :: InputNormalizer -> Decoder OverlayFile $cautoWith :: InputNormalizer -> Decoder OverlayFile FromDhall, InputNormalizer -> Encoder OverlayFile forall a. (InputNormalizer -> Encoder a) -> ToDhall a injectWith :: InputNormalizer -> Encoder OverlayFile $cinjectWith :: InputNormalizer -> Encoder OverlayFile ToDhall) $(deriveLift 'MkOverlayFile) mkOverlayFile :: FilePath -> Q Exp mkOverlayFile :: String -> Q Exp mkOverlayFile = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either (forall a. HasCallStack => String -> a error forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. Show a => a -> String show) (forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp lift forall b c a. (b -> c) -> (a -> b) -> a -> c . Path Rel File -> OverlayFile MkOverlayFile) forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *). MonadThrow m => String -> m (Path Rel File) parseRelFile