diff --git a/backend/BW/Logic.purs b/backend/BW/Logic.purs index 00ee222..4c49426 100644 --- a/backend/BW/Logic.purs +++ b/backend/BW/Logic.purs @@ -3,6 +3,7 @@ module BW.Logic where import BW import BW.Types import Prelude + import Bridge as Bridge import Control.Monad.Error.Class (throwError) import Control.Promise (Promise) @@ -31,37 +32,38 @@ import Type.Prelude (Proxy(..)) import Untagged.Union (type (|+|)) -- | Creates the master key -makePreloginKey :: - forall r. - PreloginResponse -> - Email -> - Password -> - Run - ( crypto :: - Reader CryptoService - , effect :: Effect - , aff :: Aff - | r - ) - SymmetricCryptoKey +makePreloginKey + :: forall r + . PreloginResponse + -> Email + -> Password + -> Run + ( crypto :: + Reader CryptoService + , effect :: Effect + , aff :: Aff + | r + ) + SymmetricCryptoKey makePreloginKey { kdf, kdfIterations } (Email email') password = do crypto <- askAt (Proxy :: _ "crypto") let email = (String.trim >>> String.toLower) email' liftPromise $ runFn4 crypto.makeKey password email kdf kdfIterations -makeDecryptionKey :: - forall r. +makeDecryptionKey + :: forall r + . -- | Matser key (prelogin key) - SymmetricCryptoKey -> - EncryptedString -> - Run - ( crypto :: Reader CryptoService - , effect :: Effect - , aff :: Aff - | r - ) - SymmetricCryptoKey + SymmetricCryptoKey + -> EncryptedString + -> Run + ( crypto :: Reader CryptoService + , effect :: Effect + , aff :: Aff + | r + ) + SymmetricCryptoKey makeDecryptionKey masterKey str = do crypto <- askAt (Proxy :: _ "crypto") let @@ -78,28 +80,29 @@ makeDecryptionKey masterKey str = do liftEffect $ Exc.throw $ "Unsupported key encryption type: " <> show encType pure $ SymmetricCryptoKey.fromArrayBuffer key -getLogInRequestToken :: - forall r. - { prelogin :: PreloginResponse - , email :: Email - , password :: Password - , captchaResponse :: Maybe String - , secondFactor :: Bridge.Cmd_Login_secondFactor_Maybe - } -> - Run - ( api :: Reader ApiService - , crypto :: Reader CryptoService - , effect :: Effect - , aff :: Aff - | r - ) - (IdentityCaptchaResponse |+| IdentityTwoFactorResponse |+| IdentityTokenResponse) -getLogInRequestToken { prelogin -, email -, password -, captchaResponse -, secondFactor: Bridge.Cmd_Login_secondFactor_Maybe secondFactor -} = do +getLogInRequestToken + :: forall r + . { prelogin :: PreloginResponse + , email :: Email + , password :: Password + , captchaResponse :: Maybe String + , secondFactor :: Bridge.Cmd_Login_secondFactor_Maybe + } + -> Run + ( api :: Reader ApiService + , crypto :: Reader CryptoService + , effect :: Effect + , aff :: Aff + | r + ) + (IdentityCaptchaResponse |+| IdentityTwoFactorResponse |+| IdentityTokenResponse) +getLogInRequestToken + { prelogin + , email + , password + , captchaResponse + , secondFactor: Bridge.Cmd_Login_secondFactor_Maybe secondFactor + } = do let twoFactor = maybe @@ -127,18 +130,18 @@ getLogInRequestToken { prelogin } } -bwPasswordStringHash :: - forall r. - PreloginResponse -> - Email -> - Password -> - Run - ( crypto :: Reader CryptoService - , effect :: Effect - , aff :: Aff - | r - ) - StringHash +bwPasswordStringHash + :: forall r + . PreloginResponse + -> Email + -> Password + -> Run + ( crypto :: Reader CryptoService + , effect :: Effect + , aff :: Aff + | r + ) + StringHash bwPasswordStringHash prelogin email password = do key <- makePreloginKey prelogin email password crypto <- askAt (Proxy :: _ "crypto") @@ -147,47 +150,47 @@ bwPasswordStringHash prelogin email password = do $ runFn3 crypto.hashPassword password key (nullify hashPurposeLocalAuthorization) liftPromise $ runFn3 crypto.hashPassword password key jnull -hashPassword :: - forall r. - Password -> - Run - ( cryptoFunctions :: Reader CryptoFunctions - , aff :: Aff - , effect :: Effect - | r - ) - Hash +hashPassword + :: forall r + . Password + -> Run + ( cryptoFunctions :: Reader CryptoFunctions + , aff :: Aff + , effect :: Effect + | r + ) + Hash hashPassword (Password password) = do cryptoFunctions <- askAt (Proxy :: _ "cryptoFunctions") liftPromise $ runFn2 cryptoFunctions.hash password cryptoFunctionsTypeSha512 -decrypt :: - forall r. - EncryptedString -> - Run - ( key :: Reader SymmetricCryptoKey - , crypto :: Reader CryptoService - , aff :: Aff - , effect :: Effect - | r - ) - String +decrypt + :: forall r + . EncryptedString + -> Run + ( key :: Reader SymmetricCryptoKey + , crypto :: Reader CryptoService + , aff :: Aff + , effect :: Effect + | r + ) + String decrypt input = do crypto <- askAt (Proxy :: _ "crypto") key <- askAt (Proxy :: _ "key") liftPromise $ runFn2 crypto.decryptToUtf8 (EncString.fromString input) key -encrypt :: - forall r. - String -> - Run - ( key :: Reader SymmetricCryptoKey - , crypto :: Reader CryptoService - , aff :: Aff - , effect :: Effect - | r - ) - EncryptedString +encrypt + :: forall r + . String + -> Run + ( key :: Reader SymmetricCryptoKey + , crypto :: Reader CryptoService + , aff :: Aff + , effect :: Effect + | r + ) + EncryptedString encrypt input = do crypto <- askAt (Proxy :: _ "crypto") key <- askAt (Proxy :: _ "key") @@ -196,17 +199,17 @@ encrypt input = do liftPromise :: forall m a. MonadAff m => Promise a -> m a liftPromise = liftAff <<< Promise.toAff -encodeCipher :: - forall r. - Bridge.FullCipher -> - Run - ( key :: Reader SymmetricCryptoKey - , crypto :: Reader CryptoService - , aff :: Aff - , effect :: Effect - | r - ) - CipherResponse +encodeCipher + :: forall r + . Bridge.FullCipher + -> Run + ( key :: Reader SymmetricCryptoKey + , crypto :: Reader CryptoService + , aff :: Aff + , effect :: Effect + | r + ) + CipherResponse encodeCipher (Bridge.FullCipher { name, cipher, id, favorite, reprompt, collectionIds }) = do let @@ -222,14 +225,14 @@ encodeCipher pure x { card = - nullify - { cardholderName - , brand - , number - , expMonth - , expYear - , code - } + nullify + { cardholderName + , brand + , number + , expMonth + , expYear + , code + } , type = cipherTypeCard } Bridge.IdentityCipher (Bridge.Cipher_IdentityCipher identity) -> do @@ -254,26 +257,26 @@ encodeCipher pure x { identity = - nullify - { address1 - , address2 - , address3 - , city - , company - , country - , email - , firstName - , lastName - , licenseNumber - , middleName - , passportNumber - , phone - , postalCode - , ssn - , state - , title - , username - } + nullify + { address1 + , address2 + , address3 + , city + , company + , country + , email + , firstName + , lastName + , licenseNumber + , middleName + , passportNumber + , phone + , postalCode + , ssn + , state + , title + , username + } , type = cipherTypeIdentity } Bridge.LoginCipher (Bridge.Cipher_LoginCipher login) -> do @@ -281,7 +284,7 @@ encodeCipher uris <- traverse ( \uri -> do - uriEnc <- encrypt uri + uriEnc <- nullify <$> encrypt uri pure { uri: uriEnc, match: jnull } ) (unwrap login.uris) @@ -290,14 +293,14 @@ encodeCipher pure x { login = - nullify - { password - , uris: JOpt $ opt uris - , username - , passwordRevisionDate: jnull - , totp: totp - , autofillOnPageLoad: JOpt undefined - } + nullify + { password + , uris: JOpt $ opt uris + , username + , passwordRevisionDate: jnull + , totp: totp + , autofillOnPageLoad: JOpt undefined + } , type = cipherTypeLogin } Bridge.NoteCipher note -> do @@ -332,98 +335,99 @@ encodeCipher , reprompt } -decodeCipher :: - forall r. - CipherResponse -> - Run - ( key :: Reader SymmetricCryptoKey - , crypto :: Reader CryptoService - , aff :: Aff - , effect :: Effect - | r - ) - Bridge.FullCipher +decodeCipher + :: forall r + . CipherResponse + -> Run + ( key :: Reader SymmetricCryptoKey + , crypto :: Reader CryptoService + , aff :: Aff + , effect :: Effect + | r + ) + Bridge.FullCipher decodeCipher cipher = do name <- decrypt cipher.name cipherType <- case cipher.type of n | cipherTypeSecureNote == n -> do - note <- fromJNullable "" <$> (traverse decrypt cipher.notes) - pure $ Bridge.NoteCipher note + note <- fromJNullable "" <$> (traverse decrypt cipher.notes) + pure $ Bridge.NoteCipher note n | cipherTypeLogin == n -> do - case JNullable.toMaybe cipher.login of - Nothing -> liftEffect $ throwError $ error "Login data is missing" - Just login -> do - username <- decryptNullable login.username - password <- decryptNullable login.password - totp <- decryptNullable login.totp - uris <- fromJOpt [] <$> ((traverse >>> traverse) (_.uri >>> decrypt) login.uris) - pure $ Bridge.LoginCipher - $ Bridge.Cipher_LoginCipher - { username - , password - , uris: wrap uris - , totp - } + case JNullable.toMaybe cipher.login of + Nothing -> liftEffect $ throwError $ error "Login data is missing" + Just login -> do + username <- decryptNullable login.username + password <- decryptNullable login.password + totp <- decryptNullable login.totp + uris <- fromJOpt [] <$> + ((traverse >>> traverse) (_.uri >>> JNullable.toMaybe >>> maybe (pure "") decrypt) login.uris) + pure $ Bridge.LoginCipher + $ Bridge.Cipher_LoginCipher + { username + , password + , uris: wrap uris + , totp + } n | cipherTypeCard == n -> do - case JNullable.toMaybe cipher.card of - Nothing -> liftEffect $ throwError $ error "Card data is missing" - Just card -> do - cardholderName <- decryptNullable card.cardholderName - number <- decryptNullable card.number - code <- decryptNullable card.code - brand <- decryptNullable card.brand - expMonth <- decryptNullable card.expMonth - expYear <- decryptNullable card.expYear - pure $ Bridge.CardCipher - $ Bridge.Cipher_CardCipher - { brand, cardholderName, code, expMonth, expYear, number } + case JNullable.toMaybe cipher.card of + Nothing -> liftEffect $ throwError $ error "Card data is missing" + Just card -> do + cardholderName <- decryptNullable card.cardholderName + number <- decryptNullable card.number + code <- decryptNullable card.code + brand <- decryptNullable card.brand + expMonth <- decryptNullable card.expMonth + expYear <- decryptNullable card.expYear + pure $ Bridge.CardCipher + $ Bridge.Cipher_CardCipher + { brand, cardholderName, code, expMonth, expYear, number } n | cipherTypeIdentity == n -> do - case JNullable.toMaybe cipher.identity of - Nothing -> liftEffect $ throwError $ error "Identity data is missing" - Just identity -> do - firstName <- decryptNullable identity.firstName - middleName <- decryptNullable identity.middleName - lastName <- decryptNullable identity.lastName - address1 <- decryptNullable identity.address1 - address2 <- decryptNullable identity.address2 - address3 <- decryptNullable identity.address3 - city <- decryptNullable identity.city - company <- decryptNullable identity.company - country <- decryptNullable identity.country - email <- decryptNullable identity.email - licenseNumber <- decryptNullable identity.licenseNumber - passportNumber <- decryptNullable identity.passportNumber - phone <- decryptNullable identity.phone - postalCode <- decryptNullable identity.postalCode - ssn <- decryptNullable identity.ssn - state <- decryptNullable identity.state - title <- decryptNullable identity.title - username <- decryptNullable identity.username - pure $ Bridge.IdentityCipher - $ wrap - { firstName - , middleName - , lastName - , address1 - , address2 - , address3 - , city - , company - , country - , email - , licenseNumber - , passportNumber - , phone - , postalCode - , ssn - , state - , title - , username - } + case JNullable.toMaybe cipher.identity of + Nothing -> liftEffect $ throwError $ error "Identity data is missing" + Just identity -> do + firstName <- decryptNullable identity.firstName + middleName <- decryptNullable identity.middleName + lastName <- decryptNullable identity.lastName + address1 <- decryptNullable identity.address1 + address2 <- decryptNullable identity.address2 + address3 <- decryptNullable identity.address3 + city <- decryptNullable identity.city + company <- decryptNullable identity.company + country <- decryptNullable identity.country + email <- decryptNullable identity.email + licenseNumber <- decryptNullable identity.licenseNumber + passportNumber <- decryptNullable identity.passportNumber + phone <- decryptNullable identity.phone + postalCode <- decryptNullable identity.postalCode + ssn <- decryptNullable identity.ssn + state <- decryptNullable identity.state + title <- decryptNullable identity.title + username <- decryptNullable identity.username + pure $ Bridge.IdentityCipher + $ wrap + { firstName + , middleName + , lastName + , address1 + , address2 + , address3 + , city + , company + , country + , email + , licenseNumber + , passportNumber + , phone + , postalCode + , ssn + , state + , title + , username + } n -> liftEffect $ throwError $ error $ "Unsupported cipher type: " <> show n pure $ wrap @@ -435,32 +439,32 @@ decodeCipher cipher = do , collectionIds: wrap <<< fromJNullable [] $ cipher.collectionIds } -decryptNullable :: - forall x r. - Newtype x (Maybe String) => - JNullable EncryptedString -> - Run - ( key :: Reader SymmetricCryptoKey - , crypto :: Reader CryptoService - , aff :: Aff - , effect :: Effect - | r - ) - x +decryptNullable + :: forall x r + . Newtype x (Maybe String) + => JNullable EncryptedString + -> Run + ( key :: Reader SymmetricCryptoKey + , crypto :: Reader CryptoService + , aff :: Aff + , effect :: Effect + | r + ) + x decryptNullable x = wrap <<< fromJNullable Nothing <<< map Just <$> (traverse decrypt x) -encryptNullable :: - forall x r. - Newtype x (Maybe String) => - x -> - Run - ( key :: Reader SymmetricCryptoKey - , crypto :: Reader CryptoService - , aff :: Aff - , effect :: Effect - | r - ) - (JNullable EncryptedString) +encryptNullable + :: forall x r + . Newtype x (Maybe String) + => x + -> Run + ( key :: Reader SymmetricCryptoKey + , crypto :: Reader CryptoService + , aff :: Aff + , effect :: Effect + | r + ) + (JNullable EncryptedString) encryptNullable x = case unwrap x of Nothing -> pure jnull Just y -> nullify <$> encrypt y diff --git a/backend/BW/Types.purs b/backend/BW/Types.purs index 772448b..3db6743 100644 --- a/backend/BW/Types.purs +++ b/backend/BW/Types.purs @@ -21,8 +21,7 @@ import Untagged.TypeCheck (class HasRuntimeType) import Untagged.Union (type (|+|)) import Untagged.Union as Union -newtype EncryptedString - = EncryptedString String +newtype EncryptedString = EncryptedString String derive newtype instance Show EncryptedString derive newtype instance Ord EncryptedString @@ -32,77 +31,76 @@ derive newtype instance DecodeJson EncryptedString kdfPBKDF2_SHA256 = 0 :: KDF -type KDF - = Int - -type PreloginResponse - = { kdf :: KDF - , kdfIterations :: Int - } - -type PreloginRequest - = { email :: Email - } - -type ProfileResponse - = { id :: String - , name :: JNullable String - , email :: String - , emailVerified :: Boolean - , masterPasswordHint :: JNullable String - , premiumPersonally :: Boolean - -- , premiumFromOrganization :: Boolean - , culture :: JNullable String - , twoFactorEnabled :: Boolean - , key :: EncryptedString - , privateKey :: EncryptedString - , securityStamp :: JNullable String - , forcePasswordReset :: Boolean - , usesKeyConnector :: Boolean - , organizations :: Array ProfileOrganizationResponse - , providers :: Array ProfileProviderResponse - , providerOrganizations :: Array ProfileProviderOrganizationResponse - } - -type ProfileOrganizationResponse - = { id :: String - , name :: JNullable String - , usePolicies :: JNullable Boolean - , useGroups :: JNullable Boolean - , useDirectory :: JNullable Boolean - , useEvents :: JNullable Boolean - , useTotp :: JNullable Boolean - , use2fa :: JNullable Boolean - , useApi :: JNullable Boolean - , useSso :: JNullable Boolean - , useKeyConnector :: JNullable Boolean - , useResetPassword :: JNullable Boolean - , selfHost :: JNullable Boolean - , usersGetPremium :: JNullable Boolean - , seats :: JNullable Int - , maxCollections :: JNullable Int - , maxStorageGb :: JNullable Int - , key :: JNullable String - , hasPublicAndPrivateKeys :: JNullable Boolean - , status :: JNullable OrganizationUserStatusType - , type :: JNullable OrganizationUserType - , enabled :: JNullable Boolean - , ssoBound :: JNullable Boolean - , identifier :: JNullable String - , permissions :: JNullable PermissionsApi - , resetPasswordEnrolled :: JNullable Boolean - , userId :: JNullable String - , providerId :: JNullable String - , providerName :: JNullable String - , familySponsorshipFriendlyName :: JNullable String - , familySponsorshipAvailable :: JNullable Boolean - , planProductType :: JNullable ProductType - , keyConnectorEnabled :: JNullable Boolean - , keyConnectorUrl :: JNullable String - , familySponsorshipLastSyncDate :: JNullable Timestamp - , familySponsorshipValidUntil :: JNullable Timestamp - , familySponsorshipToDelete :: JNullable Boolean - } +type KDF = Int + +type PreloginResponse = + { kdf :: KDF + , kdfIterations :: Int + } + +type PreloginRequest = + { email :: Email + } + +type ProfileResponse = + { id :: String + , name :: JNullable String + , email :: String + , emailVerified :: Boolean + , masterPasswordHint :: JNullable String + , premiumPersonally :: Boolean + -- , premiumFromOrganization :: Boolean + , culture :: JNullable String + , twoFactorEnabled :: Boolean + , key :: EncryptedString + , privateKey :: EncryptedString + , securityStamp :: JNullable String + , forcePasswordReset :: Boolean + , usesKeyConnector :: Boolean + , organizations :: Array ProfileOrganizationResponse + , providers :: Array ProfileProviderResponse + , providerOrganizations :: Array ProfileProviderOrganizationResponse + } + +type ProfileOrganizationResponse = + { id :: String + , name :: JNullable String + , usePolicies :: JNullable Boolean + , useGroups :: JNullable Boolean + , useDirectory :: JNullable Boolean + , useEvents :: JNullable Boolean + , useTotp :: JNullable Boolean + , use2fa :: JNullable Boolean + , useApi :: JNullable Boolean + , useSso :: JNullable Boolean + , useKeyConnector :: JNullable Boolean + , useResetPassword :: JNullable Boolean + , selfHost :: JNullable Boolean + , usersGetPremium :: JNullable Boolean + , seats :: JNullable Int + , maxCollections :: JNullable Int + , maxStorageGb :: JNullable Int + , key :: JNullable String + , hasPublicAndPrivateKeys :: JNullable Boolean + , status :: JNullable OrganizationUserStatusType + , type :: JNullable OrganizationUserType + , enabled :: JNullable Boolean + , ssoBound :: JNullable Boolean + , identifier :: JNullable String + , permissions :: JNullable PermissionsApi + , resetPasswordEnrolled :: JNullable Boolean + , userId :: JNullable String + , providerId :: JNullable String + , providerName :: JNullable String + , familySponsorshipFriendlyName :: JNullable String + , familySponsorshipAvailable :: JNullable Boolean + , planProductType :: JNullable ProductType + , keyConnectorEnabled :: JNullable Boolean + , keyConnectorUrl :: JNullable String + , familySponsorshipLastSyncDate :: JNullable Timestamp + , familySponsorshipValidUntil :: JNullable Timestamp + , familySponsorshipToDelete :: JNullable Boolean + } organizationUserStatusTypeInvited = 0 :: OrganizationUserStatusType @@ -110,8 +108,7 @@ organizationUserStatusTypeAccepted = 0 :: OrganizationUserStatusType organizationUserStatusTypeConfirmed = 0 :: OrganizationUserStatusType -type OrganizationUserStatusType - = Int +type OrganizationUserStatusType = Int organizationUserTypeOwner = 0 :: OrganizationUserType @@ -123,27 +120,26 @@ organizationUserTypeManager = 3 :: OrganizationUserType organizationUserTypeCustom = 4 :: OrganizationUserType -type OrganizationUserType - = Int - -type PermissionsApi - = { accessEventLogs :: Boolean - , accessImportExport :: Boolean - , accessReports :: Boolean - , manageAllCollections :: Boolean - , createNewCollections :: Boolean - , editAnyCollection :: Boolean - , deleteAnyCollection :: Boolean - , manageAssignedCollections :: Boolean - , editAssignedCollections :: Boolean - , deleteAssignedCollections :: Boolean - , manageCiphers :: Boolean - , manageGroups :: Boolean - , manageSso :: Boolean - , managePolicies :: Boolean - , manageUsers :: Boolean - , manageResetPassword :: Boolean - } +type OrganizationUserType = Int + +type PermissionsApi = + { accessEventLogs :: Boolean + , accessImportExport :: Boolean + , accessReports :: Boolean + , manageAllCollections :: Boolean + , createNewCollections :: Boolean + , editAnyCollection :: Boolean + , deleteAnyCollection :: Boolean + , manageAssignedCollections :: Boolean + , editAssignedCollections :: Boolean + , deleteAssignedCollections :: Boolean + , manageCiphers :: Boolean + , manageGroups :: Boolean + , manageSso :: Boolean + , managePolicies :: Boolean + , manageUsers :: Boolean + , manageResetPassword :: Boolean + } productTypeFree = 0 :: ProductType @@ -153,20 +149,19 @@ productTypeTeams = 2 :: ProductType productTypeEnterprise = 3 :: ProductType -type ProductType - = Int - -type ProfileProviderResponse - = { id :: String - , name :: JNullable String - , key :: JNullable String - , status :: JNullable ProviderUserStatusType - , type :: JNullable ProviderUserType - , enabled :: Boolean - , permissions :: PermissionsApi - , userId :: JNullable String - , useEvents :: Boolean - } +type ProductType = Int + +type ProfileProviderResponse = + { id :: String + , name :: JNullable String + , key :: JNullable String + , status :: JNullable ProviderUserStatusType + , type :: JNullable ProviderUserType + , enabled :: Boolean + , permissions :: PermissionsApi + , userId :: JNullable String + , useEvents :: Boolean + } providerUserStatusTypeInvited = 0 :: ProviderUserStatusType @@ -174,81 +169,79 @@ providerUserStatusTypeAccepted = 1 :: ProviderUserStatusType providerUserStatusTypeConfirmed = 2 :: ProviderUserStatusType -type ProviderUserStatusType - = Int +type ProviderUserStatusType = Int providerUserTypeProviderAdmin = 0 :: ProviderUserType providerUserTypeServiceUser = 1 :: ProviderUserType -type ProviderUserType - = Int - -type ProfileProviderOrganizationResponse - = { id :: String - , name :: JNullable String - , usePolicies :: Boolean - , useGroups :: Boolean - , useDirectory :: Boolean - , useEvents :: Boolean - , useTotp :: Boolean - , use2fa :: Boolean - , useApi :: Boolean - , useSso :: Boolean - , useKeyConnector :: Boolean - , useResetPassword :: Boolean - , selfHost :: Boolean - , usersGetPremium :: Boolean - , seats :: Int - , maxCollections :: Int - , maxStorageGb :: JNullable Int - , key :: JNullable String - , hasPublicAndPrivateKeys :: Boolean - , status :: OrganizationUserStatusType - , type :: OrganizationUserType - , enabled :: Boolean - , ssoBound :: Boolean - , identifier :: JNullable String - , permissions :: PermissionsApi - , resetPasswordEnrolled :: Boolean - , userId :: JNullable String - , providerId :: JNullable String - , providerName :: JNullable String - , familySponsorshipFriendlyName :: JNullable String - , familySponsorshipAvailable :: Boolean - , planProductType :: ProductType - , keyConnectorEnabled :: Boolean - , keyConnectorUrl :: JNullable String - , familySponsorshipLastSyncDate :: JNullable Timestamp - , familySponsorshipValidUntil :: JNullable Timestamp - , familySponsorshipToDelete :: JNullable Boolean - } - -type Urls - = { base :: JNullable String - , webVault :: JNullable String - , api :: JNullable String - , identity :: JNullable String - , icons :: JNullable String - , notifications :: JNullable String - , events :: JNullable String - , keyConnector :: JNullable String - } - -type PasswordTokenRequest - = { email :: Email - , masterPasswordHash :: String - , captchaResponse :: String - , twoFactor :: TokenRequestTwoFactor - , device :: DeviceRequest - } - -type DeviceRequest - = { type :: DeviceType - , name :: String - , identifier :: String - , pushToken :: JNullable String - } +type ProviderUserType = Int + +type ProfileProviderOrganizationResponse = + { id :: String + , name :: JNullable String + , usePolicies :: Boolean + , useGroups :: Boolean + , useDirectory :: Boolean + , useEvents :: Boolean + , useTotp :: Boolean + , use2fa :: Boolean + , useApi :: Boolean + , useSso :: Boolean + , useKeyConnector :: Boolean + , useResetPassword :: Boolean + , selfHost :: Boolean + , usersGetPremium :: Boolean + , seats :: Int + , maxCollections :: Int + , maxStorageGb :: JNullable Int + , key :: JNullable String + , hasPublicAndPrivateKeys :: Boolean + , status :: OrganizationUserStatusType + , type :: OrganizationUserType + , enabled :: Boolean + , ssoBound :: Boolean + , identifier :: JNullable String + , permissions :: PermissionsApi + , resetPasswordEnrolled :: Boolean + , userId :: JNullable String + , providerId :: JNullable String + , providerName :: JNullable String + , familySponsorshipFriendlyName :: JNullable String + , familySponsorshipAvailable :: Boolean + , planProductType :: ProductType + , keyConnectorEnabled :: Boolean + , keyConnectorUrl :: JNullable String + , familySponsorshipLastSyncDate :: JNullable Timestamp + , familySponsorshipValidUntil :: JNullable Timestamp + , familySponsorshipToDelete :: JNullable Boolean + } + +type Urls = + { base :: JNullable String + , webVault :: JNullable String + , api :: JNullable String + , identity :: JNullable String + , icons :: JNullable String + , notifications :: JNullable String + , events :: JNullable String + , keyConnector :: JNullable String + } + +type PasswordTokenRequest = + { email :: Email + , masterPasswordHash :: String + , captchaResponse :: String + , twoFactor :: TokenRequestTwoFactor + , device :: DeviceRequest + } + +type DeviceRequest = + { type :: DeviceType + , name :: String + , identifier :: String + , pushToken :: JNullable String + } deviceTypeAndroid = 0 :: DeviceType @@ -292,14 +285,13 @@ deviceTypeVivaldiExtension = 19 :: DeviceType deviceTypeSafariExtension = 20 :: DeviceType -type DeviceType - = Int +type DeviceType = Int -type TokenRequestTwoFactor - = { provider :: TwoFactorProviderType - , token :: String - , remember :: Boolean - } +type TokenRequestTwoFactor = + { provider :: TwoFactorProviderType + , token :: String + , remember :: Boolean + } twoFactorProviderTypeAuthenticator = 0 :: TwoFactorProviderType @@ -317,12 +309,11 @@ twoFactorProviderTypeOrganizationDuo = 6 :: TwoFactorProviderType twoFactorProviderTypeWebAuthn = 7 :: TwoFactorProviderType -type TwoFactorProviderType - = Int +type TwoFactorProviderType = Int -secondFactorTypeToBridge :: - TwoFactorProviderType -> - Maybe Bridge.TwoFactorProviderType +secondFactorTypeToBridge + :: TwoFactorProviderType + -> Maybe Bridge.TwoFactorProviderType secondFactorTypeToBridge x = case x of n | n == twoFactorProviderTypeAuthenticator -> Just Bridge.Authenticator @@ -352,21 +343,17 @@ bridgeToSecondFactorType Bridge.Remember = twoFactorProviderTypeRemember bridgeToSecondFactorType Bridge.OrganizationDuo = twoFactorProviderTypeOrganizationDuo bridgeToSecondFactorType Bridge.WebAuthn = twoFactorProviderTypeWebAuthn -newtype Password - = Password String +newtype Password = Password String hashPurposeServerAuthorization = 1 :: HashPurpose hashPurposeLocalAuthorization = 2 :: HashPurpose -type HashPurpose - = Int +type HashPurpose = Int -newtype StringHash - = StringHash String +newtype StringHash = StringHash String -newtype AccessToken - = AccessToken String +newtype AccessToken = AccessToken String derive newtype instance Show AccessToken derive newtype instance Eq AccessToken @@ -374,8 +361,7 @@ derive newtype instance Ord AccessToken derive newtype instance EncodeJson AccessToken derive newtype instance DecodeJson AccessToken -newtype RefreshToken - = RefreshToken String +newtype RefreshToken = RefreshToken String derive newtype instance Show RefreshToken derive newtype instance Eq RefreshToken @@ -387,21 +373,21 @@ type IdentityCaptchaResponse = { siteKey :: String } -type IdentityTokenResponse - = { accessToken :: AccessToken - , expiresIn :: Int - , refreshToken :: RefreshToken - , tokenType :: String - , resetMasterPassword :: Boolean - , privateKey :: EncryptedString - , key :: EncryptedString - , twoFactorToken :: JNullable String - , kdf :: KDF - , kdfIterations :: Int - , forcePasswordReset :: JNullable Boolean - , apiUseKeyConnector :: JNullable Boolean - , keyConnectorUrl :: JNullable String - } +type IdentityTokenResponse = + { accessToken :: AccessToken + , expiresIn :: Int + , refreshToken :: RefreshToken + , tokenType :: String + , resetMasterPassword :: Boolean + , privateKey :: EncryptedString + , key :: EncryptedString + , twoFactorToken :: JNullable String + , kdf :: KDF + , kdfIterations :: Int + , forcePasswordReset :: JNullable Boolean + , apiUseKeyConnector :: JNullable Boolean + , keyConnectorUrl :: JNullable String + } newtype TwoFactorProviderTypes = TwoFactorProviderTypes (Array (Int |+| String)) @@ -421,59 +407,57 @@ type IdentityTwoFactorResponse = , captchaToken :: String |+| Undefined } -newtype Email - = Email String - -type SyncResponse - = { profile :: ProfileResponse - , folders :: Array FolderResponse - , collections :: Array CollectionDetailsResponse - , ciphers :: Array CipherResponse - , domains :: JNullable DomainsResponse - , policies :: JNullable (Array PolicyResponse) - , sends :: Array SendResponse - } +newtype Email = Email String -type FolderResponse - = { id :: String - , name :: JNullable String - , revisionDate :: JNullable String - } +type SyncResponse = + { profile :: ProfileResponse + , folders :: Array FolderResponse + , collections :: Array CollectionDetailsResponse + , ciphers :: Array CipherResponse + , domains :: JNullable DomainsResponse + , policies :: JNullable (Array PolicyResponse) + , sends :: Array SendResponse + } -type CollectionDetailsResponse - = { id :: String - , organizationId :: JNullable String - , name :: JNullable String - , externalId :: JNullable String - , readOnly :: Boolean - } +type FolderResponse = + { id :: String + , name :: JNullable String + , revisionDate :: JNullable String + } +type CollectionDetailsResponse = + { id :: String + , organizationId :: JNullable String + , name :: JNullable String + , externalId :: JNullable String + , readOnly :: Boolean + } type CipherId = String -type CipherResponse - = { id :: CipherId - , organizationId :: JNullable String - , folderId :: JNullable String - , type :: CipherType - , name :: EncryptedString - , notes :: JNullable EncryptedString - , fields :: JNullable (Array FieldApi) - , login :: JNullable LoginApi - , card :: JNullable CardApi - , identity :: JNullable IdentityApi - , secureNote :: JNullable SecureNoteApi - , favorite :: Boolean - , edit :: JNullable Boolean - , viewPassword :: JNullable Boolean - , organizationUseTotp :: JNullable Boolean - , revisionDate :: JNullable Timestamp - , attachments :: JNullable (Array AttachmentResponse) - , passwordHistory :: JNullable (Array PasswordHistoryResponse) - , collectionIds :: JNullable (Array String) - , deletedDate :: JNullable String - , reprompt :: CipherRepromptType - } +type CipherResponse = + { id :: CipherId + , organizationId :: JNullable String + , folderId :: JNullable String + , type :: CipherType + , name :: EncryptedString + , notes :: JNullable EncryptedString + , fields :: JNullable (Array FieldApi) + , login :: JNullable LoginApi + , card :: JNullable CardApi + , identity :: JNullable IdentityApi + , secureNote :: JNullable SecureNoteApi + , favorite :: Boolean + , edit :: JNullable Boolean + , viewPassword :: JNullable Boolean + , organizationUseTotp :: JNullable Boolean + , revisionDate :: JNullable Timestamp + , attachments :: JNullable (Array AttachmentResponse) + , passwordHistory :: JNullable (Array PasswordHistoryResponse) + , collectionIds :: JNullable (Array String) + , deletedDate :: JNullable String + , reprompt :: CipherRepromptType + } cipherTypeLogin = 1 :: CipherType @@ -483,15 +467,14 @@ cipherTypeCard = 3 :: CipherType cipherTypeIdentity = 4 :: CipherType -type CipherType - = Int +type CipherType = Int -type FieldApi - = { name :: JNullable String - , value :: JNullable String - , type :: FieldType - , linkedId :: JNullable LinkedIdType - } +type FieldApi = + { name :: JNullable String + , value :: JNullable String + , type :: FieldType + , linkedId :: JNullable LinkedIdType + } fieldTypeText = 0 :: FieldType @@ -501,8 +484,7 @@ fieldTypeBoolean = 2 :: FieldType fieldTypeLinked = 3 :: FieldType -type FieldType - = Int +type FieldType = Int linkedIdTypeLoginLinkedIdUsername = 100 :: LinkedIdType @@ -558,23 +540,22 @@ linkedIdTypeIdentityLinkedIdLastName = 417 :: LinkedIdType linkedIdTypeIdentityLinkedIdFullName = 418 :: LinkedIdType -type LinkedIdType - = Int +type LinkedIdType = Int -type LoginApi - = { uris :: JOpt (Array LoginUriApi) - , username :: JNullable EncryptedString - , password :: JNullable EncryptedString - , passwordRevisionDate :: JNullable String - , totp :: JNullable EncryptedString - -- This thing is undefined in some cases for some reson. Just ignoring it - , autofillOnPageLoad :: JOpt (JNullable Boolean) - } +type LoginApi = + { uris :: JOpt (Array LoginUriApi) + , username :: JNullable EncryptedString + , password :: JNullable EncryptedString + , passwordRevisionDate :: JNullable String + , totp :: JNullable EncryptedString + -- This thing is undefined in some cases for some reson. Just ignoring it + , autofillOnPageLoad :: JOpt (JNullable Boolean) + } -type LoginUriApi - = { uri :: EncryptedString - , match :: JNullable UriMatchType - } +type LoginUriApi = + { uri :: JNullable EncryptedString + , match :: JNullable UriMatchType + } uriMatchTypeDomain = 0 :: UriMatchType @@ -588,87 +569,85 @@ uriMatchTypeRegularExpression = 4 :: UriMatchType uriMatchTypeNever = 5 :: UriMatchType -type UriMatchType - = Int - -type CardApi - = { cardholderName :: JNullable EncryptedString - , brand :: JNullable EncryptedString - , number :: JNullable EncryptedString - , expMonth :: JNullable EncryptedString - , expYear :: JNullable EncryptedString - , code :: JNullable EncryptedString - } - -type IdentityApi - = { title :: JNullable EncryptedString - , firstName :: JNullable EncryptedString - , middleName :: JNullable EncryptedString - , lastName :: JNullable EncryptedString - , address1 :: JNullable EncryptedString - , address2 :: JNullable EncryptedString - , address3 :: JNullable EncryptedString - , city :: JNullable EncryptedString - , state :: JNullable EncryptedString - , postalCode :: JNullable EncryptedString - , country :: JNullable EncryptedString - , company :: JNullable EncryptedString - , email :: JNullable EncryptedString - , phone :: JNullable EncryptedString - , ssn :: JNullable EncryptedString - , username :: JNullable EncryptedString - , passportNumber :: JNullable EncryptedString - , licenseNumber :: JNullable EncryptedString - } +type UriMatchType = Int + +type CardApi = + { cardholderName :: JNullable EncryptedString + , brand :: JNullable EncryptedString + , number :: JNullable EncryptedString + , expMonth :: JNullable EncryptedString + , expYear :: JNullable EncryptedString + , code :: JNullable EncryptedString + } + +type IdentityApi = + { title :: JNullable EncryptedString + , firstName :: JNullable EncryptedString + , middleName :: JNullable EncryptedString + , lastName :: JNullable EncryptedString + , address1 :: JNullable EncryptedString + , address2 :: JNullable EncryptedString + , address3 :: JNullable EncryptedString + , city :: JNullable EncryptedString + , state :: JNullable EncryptedString + , postalCode :: JNullable EncryptedString + , country :: JNullable EncryptedString + , company :: JNullable EncryptedString + , email :: JNullable EncryptedString + , phone :: JNullable EncryptedString + , ssn :: JNullable EncryptedString + , username :: JNullable EncryptedString + , passportNumber :: JNullable EncryptedString + , licenseNumber :: JNullable EncryptedString + } secureNoteTypeGeneric = 0 :: SecureNoteType -type SecureNoteType - = Int +type SecureNoteType = Int -type SecureNoteApi = { +type SecureNoteApi = + { -- type :: SecureNoteType -} - -type AttachmentResponse - = { id :: String - , url :: JNullable String - , fileName :: JNullable String - , key :: JNullable String - , size :: JNullable String - , sizeName :: JNullable String - } - -type PasswordHistoryResponse - = { password :: String - , lastUsedDate :: JNullable String - } + } + +type AttachmentResponse = + { id :: String + , url :: JNullable String + , fileName :: JNullable String + , key :: JNullable String + , size :: JNullable String + , sizeName :: JNullable String + } + +type PasswordHistoryResponse = + { password :: String + , lastUsedDate :: JNullable String + } cipherRepromptTypeNone = 0 :: CipherRepromptType cipherRepromptTypePassword = 1 :: CipherRepromptType -type CipherRepromptType - = Int +type CipherRepromptType = Int -type DomainsResponse - = { equivalentDomains :: Array (Array String) - , globalEquivalentDomains :: Array GlobalDomainResponse - } +type DomainsResponse = + { equivalentDomains :: Array (Array String) + , globalEquivalentDomains :: Array GlobalDomainResponse + } -type GlobalDomainResponse - = { type :: Int - , domains :: Array String - , excluded :: Boolean - } +type GlobalDomainResponse = + { type :: Int + , domains :: Array String + , excluded :: Boolean + } -type PolicyResponse - = { id :: String - , organizationId :: JNullable String - , type :: PolicyType - , data :: ShowableJson - , enabled :: Boolean - } +type PolicyResponse = + { id :: String + , organizationId :: JNullable String + , type :: PolicyType + , data :: ShowableJson + , enabled :: Boolean + } policyTypeTwoFactorAuthentication = 0 :: PolicyType -- Requires users to have 2fa enabled @@ -692,46 +671,44 @@ policyTypeMaximumVaultTimeout = 9 :: PolicyType -- Sets the maximum allowed vaul policyTypeDisablePersonalVaultExport = 10 :: PolicyType -- Disable personal vault export -type PolicyType - = Int - -type SendResponse - = { id :: String - , accessId :: JNullable String - , type :: SendType - , name :: JNullable String - , notes :: JNullable String - , file :: JNullable SendFileApi - , text :: JNullable SendTextApi - , key :: JNullable String - , maxAccessCount :: JNullable Int - , accessCount :: JNullable Int - , revisionDate :: JNullable String - , expirationDate :: JNullable String - , deletionDate :: JNullable String - , password :: JNullable String - , disable :: Boolean - , hideEmail :: Boolean - } +type PolicyType = Int + +type SendResponse = + { id :: String + , accessId :: JNullable String + , type :: SendType + , name :: JNullable String + , notes :: JNullable String + , file :: JNullable SendFileApi + , text :: JNullable SendTextApi + , key :: JNullable String + , maxAccessCount :: JNullable Int + , accessCount :: JNullable Int + , revisionDate :: JNullable String + , expirationDate :: JNullable String + , deletionDate :: JNullable String + , password :: JNullable String + , disable :: Boolean + , hideEmail :: Boolean + } sendTypeText = 0 :: SendType sendTypeFile = 1 :: SendType -type SendType - = Int +type SendType = Int -type SendFileApi - = { id :: String - , fileName :: JNullable String - , size :: JNullable String - , sizeName :: JNullable String - } +type SendFileApi = + { id :: String + , fileName :: JNullable String + , size :: JNullable String + , sizeName :: JNullable String + } -type SendTextApi - = { text :: JNullable String - , hidden :: Boolean - } +type SendTextApi = + { text :: JNullable String + , hidden :: Boolean + } type TwoFactorEmailRequest = { email :: Email