{-# LANGUAGE UndecidableInstances #-}

module Ema.Asset (
  Asset (..),
  Format (..),
) where

-- | The type of assets that can be bundled in a static site.
data Asset a
  = -- | A file that is copied as-is from the source directory.
    --
    -- Relative paths are assumed relative to the source directory. Absolute
    -- paths allow copying static files outside of source directory.
    AssetStatic FilePath
  | -- | A file whose contents are generated at runtime by user code.
    AssetGenerated Format a
  deriving stock (Asset a -> Asset a -> Bool
forall a. Eq a => Asset a -> Asset a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Asset a -> Asset a -> Bool
$c/= :: forall a. Eq a => Asset a -> Asset a -> Bool
== :: Asset a -> Asset a -> Bool
$c== :: forall a. Eq a => Asset a -> Asset a -> Bool
Eq, Int -> Asset a -> ShowS
forall a. Show a => Int -> Asset a -> ShowS
forall a. Show a => [Asset a] -> ShowS
forall a. Show a => Asset a -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Asset a] -> ShowS
$cshowList :: forall a. Show a => [Asset a] -> ShowS
show :: Asset a -> FilePath
$cshow :: forall a. Show a => Asset a -> FilePath
showsPrec :: Int -> Asset a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Asset a -> ShowS
Show, Asset a -> Asset a -> Bool
Asset a -> Asset a -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (Asset a)
forall a. Ord a => Asset a -> Asset a -> Bool
forall a. Ord a => Asset a -> Asset a -> Ordering
forall a. Ord a => Asset a -> Asset a -> Asset a
min :: Asset a -> Asset a -> Asset a
$cmin :: forall a. Ord a => Asset a -> Asset a -> Asset a
max :: Asset a -> Asset a -> Asset a
$cmax :: forall a. Ord a => Asset a -> Asset a -> Asset a
>= :: Asset a -> Asset a -> Bool
$c>= :: forall a. Ord a => Asset a -> Asset a -> Bool
> :: Asset a -> Asset a -> Bool
$c> :: forall a. Ord a => Asset a -> Asset a -> Bool
<= :: Asset a -> Asset a -> Bool
$c<= :: forall a. Ord a => Asset a -> Asset a -> Bool
< :: Asset a -> Asset a -> Bool
$c< :: forall a. Ord a => Asset a -> Asset a -> Bool
compare :: Asset a -> Asset a -> Ordering
$ccompare :: forall a. Ord a => Asset a -> Asset a -> Ordering
Ord, forall a b. a -> Asset b -> Asset a
forall a b. (a -> b) -> Asset a -> Asset b
forall (f :: Type -> Type).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Asset b -> Asset a
$c<$ :: forall a b. a -> Asset b -> Asset a
fmap :: forall a b. (a -> b) -> Asset a -> Asset b
$cfmap :: forall a b. (a -> b) -> Asset a -> Asset b
Functor, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Asset a) x -> Asset a
forall a x. Asset a -> Rep (Asset a) x
$cto :: forall a x. Rep (Asset a) x -> Asset a
$cfrom :: forall a x. Asset a -> Rep (Asset a) x
Generic)

-- | The format of a generated asset.
data Format
  = -- | Html assets are served by the live server with hot-reload
    Html
  | -- | Other assets are served by the live server as static files.
    Other
  deriving stock (Format -> Format -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Format -> Format -> Bool
$c/= :: Format -> Format -> Bool
== :: Format -> Format -> Bool
$c== :: Format -> Format -> Bool
Eq, Int -> Format -> ShowS
[Format] -> ShowS
Format -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Format] -> ShowS
$cshowList :: [Format] -> ShowS
show :: Format -> FilePath
$cshow :: Format -> FilePath
showsPrec :: Int -> Format -> ShowS
$cshowsPrec :: Int -> Format -> ShowS
Show, Eq Format
Format -> Format -> Bool
Format -> Format -> Ordering
Format -> Format -> Format
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Format -> Format -> Format
$cmin :: Format -> Format -> Format
max :: Format -> Format -> Format
$cmax :: Format -> Format -> Format
>= :: Format -> Format -> Bool
$c>= :: Format -> Format -> Bool
> :: Format -> Format -> Bool
$c> :: Format -> Format -> Bool
<= :: Format -> Format -> Bool
$c<= :: Format -> Format -> Bool
< :: Format -> Format -> Bool
$c< :: Format -> Format -> Bool
compare :: Format -> Format -> Ordering
$ccompare :: Format -> Format -> Ordering
Ord, forall x. Rep Format x -> Format
forall x. Format -> Rep Format x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Format x -> Format
$cfrom :: forall x. Format -> Rep Format x
Generic)