module Cachix.Api.Types where
import Control.DeepSeq (NFData)
import Data.Aeson (FromJSON, ToJSON)
import Data.Monoid ((<>))
import Data.Swagger (ToParamSchema, ToSchema)
import Data.Text (Text, dropEnd, takeEnd)
import GHC.Generics (Generic)
import Servant.API
data NixCacheInfo
= NixCacheInfo
{ storeDir :: Text,
wantMassQuery :: Integer,
priority :: Integer
}
deriving (Generic, Show, FromJSON, ToJSON, ToSchema)
data NarInfo
= NarInfo
{ storePath :: Text,
url :: Text,
compression :: Text,
fileHash :: Text,
fileSize :: Integer,
narHash :: Text,
narSize :: Integer,
references :: [Text],
deriver :: Text,
sig :: Text
}
deriving (Generic, Show, FromJSON, ToJSON, ToSchema)
data BinaryCache
= BinaryCache
{ name :: Text,
uri :: Text,
isPublic :: Bool,
publicSigningKeys :: [Text],
githubUsername :: Text
}
deriving (Show, Generic, FromJSON, ToJSON, ToSchema, NFData)
newtype BinaryCacheError
= BinaryCacheError
{ error :: Text
}
deriving (Generic, FromJSON, ToJSON)
newtype NarC = NarC Text deriving (Generic, ToSchema, ToParamSchema)
instance FromHttpApiData NarC where
parseUrlPiece s =
if takeEnd 7 s == ".nar.xz"
then Right $ NarC (dropEnd 7 s)
else Left ""
instance ToHttpApiData NarC where
toUrlPiece (NarC n) = n <> ".nar.xz"
newtype NarInfoC = NarInfoC Text deriving (Generic, ToSchema, ToParamSchema)
instance FromHttpApiData NarInfoC where
parseUrlPiece s =
if takeEnd 8 s == ".narinfo"
then Right $ NarInfoC (dropEnd 8 s)
else Left ""
instance ToHttpApiData NarInfoC where
toUrlPiece (NarInfoC n) = n <> ".narinfo"
data User
= User
{ fullname :: Maybe Text,
username :: Text,
email :: Maybe Text,
hasOrgsAcccess :: Bool,
activeSubscription :: SubscriptionType,
subscriptionAccountId :: Maybe Text
}
deriving (Generic, FromJSON, ToJSON, ToSchema)
data SubscriptionType = Community | Starter | Basic | Pro
deriving (Generic, FromJSON, ToJSON, ToSchema, Show, Read)