{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE StrictData #-}
module Headroom.Types
(
HeadroomError(..)
, fromHeadroomError
, toHeadroomError
, CurrentYear(..)
, LicenseType(..)
)
where
import Data.Aeson ( FromJSON(..)
, Value(String)
)
import Data.Typeable ( cast )
import Headroom.Data.EnumExtra ( EnumExtra(..) )
import RIO
import qualified RIO.Text as T
data HeadroomError = forall e . Exception e => HeadroomError e
instance Show HeadroomError where
show :: HeadroomError -> String
show (HeadroomError e
he) = e -> String
forall a. Show a => a -> String
show e
he
instance Exception HeadroomError where
displayException :: HeadroomError -> String
displayException (HeadroomError e
he) = e -> String
forall e. Exception e => e -> String
displayException e
he
toHeadroomError :: Exception e
=> e
-> SomeException
toHeadroomError :: e -> SomeException
toHeadroomError = HeadroomError -> SomeException
forall e. Exception e => e -> SomeException
toException (HeadroomError -> SomeException)
-> (e -> HeadroomError) -> e -> SomeException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> HeadroomError
forall e. Exception e => e -> HeadroomError
HeadroomError
fromHeadroomError :: Exception e
=> SomeException
-> Maybe e
fromHeadroomError :: SomeException -> Maybe e
fromHeadroomError SomeException
e = do
HeadroomError e
he <- SomeException -> Maybe HeadroomError
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e
e -> Maybe e
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast e
he
newtype CurrentYear = CurrentYear
{ CurrentYear -> Integer
unCurrentYear :: Integer
}
deriving (CurrentYear -> CurrentYear -> Bool
(CurrentYear -> CurrentYear -> Bool)
-> (CurrentYear -> CurrentYear -> Bool) -> Eq CurrentYear
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CurrentYear -> CurrentYear -> Bool
$c/= :: CurrentYear -> CurrentYear -> Bool
== :: CurrentYear -> CurrentYear -> Bool
$c== :: CurrentYear -> CurrentYear -> Bool
Eq, Int -> CurrentYear -> ShowS
[CurrentYear] -> ShowS
CurrentYear -> String
(Int -> CurrentYear -> ShowS)
-> (CurrentYear -> String)
-> ([CurrentYear] -> ShowS)
-> Show CurrentYear
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CurrentYear] -> ShowS
$cshowList :: [CurrentYear] -> ShowS
show :: CurrentYear -> String
$cshow :: CurrentYear -> String
showsPrec :: Int -> CurrentYear -> ShowS
$cshowsPrec :: Int -> CurrentYear -> ShowS
Show)
data LicenseType
= Apache2
| BSD3
| GPL2
| GPL3
| MIT
| MPL2
deriving (LicenseType
LicenseType -> LicenseType -> Bounded LicenseType
forall a. a -> a -> Bounded a
maxBound :: LicenseType
$cmaxBound :: LicenseType
minBound :: LicenseType
$cminBound :: LicenseType
Bounded, Int -> LicenseType
LicenseType -> Int
LicenseType -> [LicenseType]
LicenseType -> LicenseType
LicenseType -> LicenseType -> [LicenseType]
LicenseType -> LicenseType -> LicenseType -> [LicenseType]
(LicenseType -> LicenseType)
-> (LicenseType -> LicenseType)
-> (Int -> LicenseType)
-> (LicenseType -> Int)
-> (LicenseType -> [LicenseType])
-> (LicenseType -> LicenseType -> [LicenseType])
-> (LicenseType -> LicenseType -> [LicenseType])
-> (LicenseType -> LicenseType -> LicenseType -> [LicenseType])
-> Enum LicenseType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: LicenseType -> LicenseType -> LicenseType -> [LicenseType]
$cenumFromThenTo :: LicenseType -> LicenseType -> LicenseType -> [LicenseType]
enumFromTo :: LicenseType -> LicenseType -> [LicenseType]
$cenumFromTo :: LicenseType -> LicenseType -> [LicenseType]
enumFromThen :: LicenseType -> LicenseType -> [LicenseType]
$cenumFromThen :: LicenseType -> LicenseType -> [LicenseType]
enumFrom :: LicenseType -> [LicenseType]
$cenumFrom :: LicenseType -> [LicenseType]
fromEnum :: LicenseType -> Int
$cfromEnum :: LicenseType -> Int
toEnum :: Int -> LicenseType
$ctoEnum :: Int -> LicenseType
pred :: LicenseType -> LicenseType
$cpred :: LicenseType -> LicenseType
succ :: LicenseType -> LicenseType
$csucc :: LicenseType -> LicenseType
Enum, Bounded LicenseType
Enum LicenseType
Eq LicenseType
Ord LicenseType
Show LicenseType
[LicenseType]
Text
Bounded LicenseType
-> Enum LicenseType
-> Eq LicenseType
-> Ord LicenseType
-> Show LicenseType
-> [LicenseType]
-> Text
-> (LicenseType -> Text)
-> (Text -> Maybe LicenseType)
-> EnumExtra LicenseType
Text -> Maybe LicenseType
LicenseType -> Text
forall a.
Bounded a
-> Enum a
-> Eq a
-> Ord a
-> Show a
-> [a]
-> Text
-> (a -> Text)
-> (Text -> Maybe a)
-> EnumExtra a
textToEnum :: Text -> Maybe LicenseType
$ctextToEnum :: Text -> Maybe LicenseType
enumToText :: LicenseType -> Text
$cenumToText :: LicenseType -> Text
allValuesToText :: Text
$callValuesToText :: Text
allValues :: [LicenseType]
$callValues :: [LicenseType]
$cp5EnumExtra :: Show LicenseType
$cp4EnumExtra :: Ord LicenseType
$cp3EnumExtra :: Eq LicenseType
$cp2EnumExtra :: Enum LicenseType
$cp1EnumExtra :: Bounded LicenseType
EnumExtra, LicenseType -> LicenseType -> Bool
(LicenseType -> LicenseType -> Bool)
-> (LicenseType -> LicenseType -> Bool) -> Eq LicenseType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LicenseType -> LicenseType -> Bool
$c/= :: LicenseType -> LicenseType -> Bool
== :: LicenseType -> LicenseType -> Bool
$c== :: LicenseType -> LicenseType -> Bool
Eq, Eq LicenseType
Eq LicenseType
-> (LicenseType -> LicenseType -> Ordering)
-> (LicenseType -> LicenseType -> Bool)
-> (LicenseType -> LicenseType -> Bool)
-> (LicenseType -> LicenseType -> Bool)
-> (LicenseType -> LicenseType -> Bool)
-> (LicenseType -> LicenseType -> LicenseType)
-> (LicenseType -> LicenseType -> LicenseType)
-> Ord LicenseType
LicenseType -> LicenseType -> Bool
LicenseType -> LicenseType -> Ordering
LicenseType -> LicenseType -> LicenseType
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 :: LicenseType -> LicenseType -> LicenseType
$cmin :: LicenseType -> LicenseType -> LicenseType
max :: LicenseType -> LicenseType -> LicenseType
$cmax :: LicenseType -> LicenseType -> LicenseType
>= :: LicenseType -> LicenseType -> Bool
$c>= :: LicenseType -> LicenseType -> Bool
> :: LicenseType -> LicenseType -> Bool
$c> :: LicenseType -> LicenseType -> Bool
<= :: LicenseType -> LicenseType -> Bool
$c<= :: LicenseType -> LicenseType -> Bool
< :: LicenseType -> LicenseType -> Bool
$c< :: LicenseType -> LicenseType -> Bool
compare :: LicenseType -> LicenseType -> Ordering
$ccompare :: LicenseType -> LicenseType -> Ordering
$cp1Ord :: Eq LicenseType
Ord, Int -> LicenseType -> ShowS
[LicenseType] -> ShowS
LicenseType -> String
(Int -> LicenseType -> ShowS)
-> (LicenseType -> String)
-> ([LicenseType] -> ShowS)
-> Show LicenseType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LicenseType] -> ShowS
$cshowList :: [LicenseType] -> ShowS
show :: LicenseType -> String
$cshow :: LicenseType -> String
showsPrec :: Int -> LicenseType -> ShowS
$cshowsPrec :: Int -> LicenseType -> ShowS
Show)
instance FromJSON LicenseType where
parseJSON :: Value -> Parser LicenseType
parseJSON = \case
String Text
s -> case Text -> Maybe LicenseType
forall a. EnumExtra a => Text -> Maybe a
textToEnum Text
s of
Just LicenseType
licenseType -> LicenseType -> Parser LicenseType
forall (f :: * -> *) a. Applicative f => a -> f a
pure LicenseType
licenseType
Maybe LicenseType
_ -> String -> Parser LicenseType
forall a. HasCallStack => String -> a
error (String -> Parser LicenseType) -> String -> Parser LicenseType
forall a b. (a -> b) -> a -> b
$ String
"Unknown license type: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
s
Value
other -> String -> Parser LicenseType
forall a. HasCallStack => String -> a
error (String -> Parser LicenseType) -> String -> Parser LicenseType
forall a b. (a -> b) -> a -> b
$ String
"Invalid value for run mode: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Value -> String
forall a. Show a => a -> String
show Value
other