ema-0.10.0.0: Static site generator library with hot reload
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ema.CLI

Synopsis

Documentation

newtype Host Source #

Host string to start the server on.

Constructors

Host 

Fields

Instances

Instances details
IsString Host Source # 
Instance details

Defined in Ema.CLI

Methods

fromString :: String -> Host #

Show Host Source # 
Instance details

Defined in Ema.CLI

Methods

showsPrec :: Int -> Host -> ShowS #

show :: Host -> String #

showList :: [Host] -> ShowS #

Default Host Source # 
Instance details

Defined in Ema.CLI

Methods

def :: Host #

Eq Host Source # 
Instance details

Defined in Ema.CLI

Methods

(==) :: Host -> Host -> Bool #

(/=) :: Host -> Host -> Bool #

Ord Host Source # 
Instance details

Defined in Ema.CLI

Methods

compare :: Host -> Host -> Ordering #

(<) :: Host -> Host -> Bool #

(<=) :: Host -> Host -> Bool #

(>) :: Host -> Host -> Bool #

(>=) :: Host -> Host -> Bool #

max :: Host -> Host -> Host #

min :: Host -> Host -> Host #

data Action result where Source #

CLI subcommand

Constructors

Generate :: FilePath -> Action [FilePath]

Generate static files at the given output directory, returning the list of generated files.

Run :: (Host, Maybe Port) -> Action ()

Run the live server

Instances

Instances details
GCompare Action Source # 
Instance details

Defined in Ema.CLI

Methods

gcompare :: forall (a :: k) (b :: k). Action a -> Action b -> GOrdering a b #

GEq Action Source # 
Instance details

Defined in Ema.CLI

Methods

geq :: forall (a :: k) (b :: k). Action a -> Action b -> Maybe (a :~: b) #

GShow Action Source # 
Instance details

Defined in Ema.CLI

Methods

gshowsPrec :: forall (a :: k). Int -> Action a -> ShowS #

ArgDict (c :: Type -> Constraint) Action Source # 
Instance details

Defined in Ema.CLI

Associated Types

type ConstraintsFor Action c #

Methods

argDict :: forall (a :: k). ConstraintsFor Action c => Action a -> Dict (c a) #

type ConstraintsFor Action (c :: Type -> Constraint) Source # 
Instance details

Defined in Ema.CLI

type ConstraintsFor Action (c :: Type -> Constraint) = (c [FilePath], c ())

data Cli Source #

Ema's command-line interface options

Constructors

Cli 

Fields

Instances

Instances details
Show Cli Source # 
Instance details

Defined in Ema.CLI

Methods

showsPrec :: Int -> Cli -> ShowS #

show :: Cli -> String #

showList :: [Cli] -> ShowS #

Default Cli Source # 
Instance details

Defined in Ema.CLI

Methods

def :: Cli #

Eq Cli Source # 
Instance details

Defined in Ema.CLI

Methods

(==) :: Cli -> Cli -> Bool #

(/=) :: Cli -> Cli -> Bool #

cliAction :: IO Cli Source #

Parse Ema CLI arguments passed by the user.

crash :: (MonadLoggerIO m, MonadFail m) => LogSource -> Text -> m a Source #

Crash the program with the given error message

First log the message using Error level, and then exit using fail.