module CabalGild.Unstable.Type.Mode where

import qualified CabalGild.Unstable.Exception.InvalidMode as InvalidMode
import qualified Control.Monad.Catch as Exception

-- | Represents the mode of the command line utility.
data Mode
  = -- | Just determine if the input is already formatted.
    Check
  | -- | Format the input.
    Format
  deriving (Mode -> Mode -> Bool
(Mode -> Mode -> Bool) -> (Mode -> Mode -> Bool) -> Eq Mode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Mode -> Mode -> Bool
== :: Mode -> Mode -> Bool
$c/= :: Mode -> Mode -> Bool
/= :: Mode -> Mode -> Bool
Eq, Int -> Mode -> ShowS
[Mode] -> ShowS
Mode -> String
(Int -> Mode -> ShowS)
-> (Mode -> String) -> ([Mode] -> ShowS) -> Show Mode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Mode -> ShowS
showsPrec :: Int -> Mode -> ShowS
$cshow :: Mode -> String
show :: Mode -> String
$cshowList :: [Mode] -> ShowS
showList :: [Mode] -> ShowS
Show)

-- | Attempts to parse a string as a mode.
fromString :: (Exception.MonadThrow m) => String -> m Mode
fromString :: forall (m :: * -> *). MonadThrow m => String -> m Mode
fromString String
s = case String
s of
  String
"check" -> Mode -> m Mode
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Mode
Check
  String
"format" -> Mode -> m Mode
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Mode
Format
  String
_ -> InvalidMode -> m Mode
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
Exception.throwM (InvalidMode -> m Mode) -> InvalidMode -> m Mode
forall a b. (a -> b) -> a -> b
$ String -> InvalidMode
InvalidMode.fromString String
s