diff options
Diffstat (limited to 'overlays/spm/server/Spm/Server/Database.hs')
| -rw-r--r-- | overlays/spm/server/Spm/Server/Database.hs | 73 | 
1 files changed, 73 insertions, 0 deletions
| diff --git a/overlays/spm/server/Spm/Server/Database.hs b/overlays/spm/server/Spm/Server/Database.hs new file mode 100644 index 00000000..cc133e06 --- /dev/null +++ b/overlays/spm/server/Spm/Server/Database.hs | |||
| @@ -0,0 +1,73 @@ | |||
| 1 | {-# LANGUAGE OverloadedStrings, TemplateHaskell, QuasiQuotes, UndecidableInstances #-} | ||
| 2 | |||
| 3 | module Spm.Server.Database | ||
| 4 | ( MailMailbox, MailLocal, MailExtension, MailDomain | ||
| 5 | , Mailbox(..), MailboxMapping(..) | ||
| 6 | , Key(..), EntityField(..), Unique(..) | ||
| 7 | ) where | ||
| 8 | |||
| 9 | import Prelude | ||
| 10 | |||
| 11 | import Database.Persist | ||
| 12 | import Database.Persist.Sql | ||
| 13 | import Database.Persist.TH | ||
| 14 | |||
| 15 | import GHC.Generics (Generic) | ||
| 16 | import Type.Reflection (Typeable) | ||
| 17 | |||
| 18 | import Data.Text (Text) | ||
| 19 | |||
| 20 | import Data.CaseInsensitive (CI) | ||
| 21 | import qualified Data.CaseInsensitive as CI | ||
| 22 | import Data.CaseInsensitive.Instances () | ||
| 23 | |||
| 24 | import Data.UUID (UUID) | ||
| 25 | import Data.UUID.Instances () | ||
| 26 | |||
| 27 | import Data.Int (Int64) | ||
| 28 | |||
| 29 | import Control.Lens | ||
| 30 | |||
| 31 | import Web.HttpApiData | ||
| 32 | |||
| 33 | |||
| 34 | newtype MailMailbox = MailMailbox | ||
| 35 | { unMailMailbox :: CI Text | ||
| 36 | } deriving stock (Eq, Ord, Read, Show, Generic, Typeable) | ||
| 37 | deriving newtype (PersistField, PersistFieldSql) | ||
| 38 | makeWrapped ''MailMailbox | ||
| 39 | newtype MailLocal = MailLocal | ||
| 40 | { unMailLocal :: CI Text | ||
| 41 | } deriving stock (Eq, Ord, Read, Show, Generic, Typeable) | ||
| 42 | deriving newtype (PersistField, PersistFieldSql) | ||
| 43 | makeWrapped ''MailLocal | ||
| 44 | newtype MailExtension = MailExtension | ||
| 45 | { unMailExtension :: CI Text | ||
| 46 | } deriving stock (Eq, Ord, Read, Show, Generic, Typeable) | ||
| 47 | deriving newtype (PersistField, PersistFieldSql) | ||
| 48 | makeWrapped ''MailExtension | ||
| 49 | newtype MailDomain = MailDomain | ||
| 50 | { unMailDomain :: CI Text | ||
| 51 | } deriving stock (Eq, Ord, Read, Show, Generic, Typeable) | ||
| 52 | deriving newtype (PersistField, PersistFieldSql) | ||
| 53 | makeWrapped ''MailDomain | ||
| 54 | |||
| 55 | instance FromHttpApiData MailDomain where | ||
| 56 | parseUrlPiece = fmap (review _Wrapped . CI.mk) . parseUrlPiece | ||
| 57 | |||
| 58 | |||
| 59 | share [mkPersist sqlSettings] [persistLowerCase| | ||
| 60 | Mailbox | ||
| 61 | Id UUID sqltype=uuid default=gen_random_uuid() | ||
| 62 | ident MailMailbox sql=mailbox | ||
| 63 | quota Int64 Maybe sql=quota_bytes MigrationOnly | ||
| 64 | UniqueMailbox ident | ||
| 65 | deriving Show | ||
| 66 | MailboxMapping | ||
| 67 | Id UUID sqltype=uuid default=gen_random_uuid() | ||
| 68 | local MailLocal Maybe | ||
| 69 | extension MailExtension Maybe | ||
| 70 | domain MailDomain | ||
| 71 | mailbox MailboxId | ||
| 72 | UniqueLocalDomain local domain sql=local_domain_unique !force | ||
| 73 | |] | ||
