{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE BinaryLiterals #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveLift #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DerivingVia #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE GeneralisedNewtypeDeriving #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE NumericUnderscores #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PackageImports #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE StrictData #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeSynonymInstances #-} module Data.Multibase.Types.Internal.IsCodec ( module Data.Multibase.Types.Internal.IsCodec , module M ) where import Data.Multibase.Types.Internal.IsCodec.Base64Pad as M import Data.Multibase.Types.Internal.IsCodec.Kit as M codecDocs :: MbAlgorithm -> CodecDocs codecDocs = dispatching mbDocs codecIsComplete :: MbAlgorithm -> Bool codecIsComplete = dispatching isCodecComplete ---------------------------------------------------------------------------------------------------- -- dispatching ---------------------------------------------------------------------------------------------------- dispatching :: forall o . (forall a . IsCodec a => Proxy a -> o) -> MbAlgorithm -> o dispatching bdy mba = case mba of MbIdentityBase -> bdy $ Proxy @IdentityBase MbBase2 -> bdy $ Proxy @Base2 MbBase8 -> bdy $ Proxy @Base8 MbBase10 -> bdy $ Proxy @Base10 MbBase16Lower -> bdy $ Proxy @Base16Lower MbBase16Upper -> bdy $ Proxy @Base16Upper MbBase32HexNoPadLower -> bdy $ Proxy @Base32HexNoPadLower MbBase32HexNoPadUpper -> bdy $ Proxy @Base32HexNoPadUpper MbBase32NoPadLower -> bdy $ Proxy @Base32NoPadLower MbBase32NoPadUpper -> bdy $ Proxy @Base32NoPadUpper MbBase32HexPadLower -> bdy $ Proxy @Base32HexPadLower MbBase32HexPadUpper -> bdy $ Proxy @Base32HexPadUpper MbBase32PadLower -> bdy $ Proxy @Base32PadLower MbBase32PadUpper -> bdy $ Proxy @Base32PadUpper MbBase32z -> bdy $ Proxy @Base32z MbBase36Lower -> bdy $ Proxy @Base36Lower MbBase36Upper -> bdy $ Proxy @Base36Upper MbBase58Btc -> bdy $ Proxy @Base58Btc MbBase58Flickr -> bdy $ Proxy @Base58Flickr MbBase64NoPad -> bdy $ Proxy @Base64NoPad MbBase64Pad -> bdy $ Proxy @Base64Pad MbBase64UrlNoPad -> bdy $ Proxy @Base64UrlNoPad MbBase64urlPad -> bdy $ Proxy @Base64urlPad MbProquint -> bdy $ Proxy @Proquint MbBase256Emoji -> bdy $ Proxy @Base256Emoji {-# INLINE dispatching #-} ---------------------------------------------------------------------------------------------------- -- IdentityBase stub ---------------------------------------------------------------------------------------------------- newtype IdentityBase = IdentityBase { getIdentityBase :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec IdentityBase where isCodecM = noCodecM MbIdentityBase ---------------------------------------------------------------------------------------------------- -- Base2 stub ---------------------------------------------------------------------------------------------------- newtype Base2 = Base2 { getBase2 :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base2 where isCodecM = noCodecM MbBase2 ---------------------------------------------------------------------------------------------------- -- Base8 stub ---------------------------------------------------------------------------------------------------- newtype Base8 = Base8 { getBase8 :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base8 where isCodecM = noCodecM MbBase8 ---------------------------------------------------------------------------------------------------- -- Base10 stub ---------------------------------------------------------------------------------------------------- newtype Base10 = Base10 { getBase10 :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base10 where isCodecM = noCodecM MbBase10 ---------------------------------------------------------------------------------------------------- -- Base16Lower stub ---------------------------------------------------------------------------------------------------- newtype Base16Lower = Base16Lower { getBase16Lower :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base16Lower where isCodecM = noCodecM MbBase16Lower ---------------------------------------------------------------------------------------------------- -- Base16Upper stub ---------------------------------------------------------------------------------------------------- newtype Base16Upper = Base16Upper { getBase16Upper :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base16Upper where isCodecM = noCodecM MbBase16Upper ---------------------------------------------------------------------------------------------------- -- Base32HexNoPadLower stub ---------------------------------------------------------------------------------------------------- newtype Base32HexNoPadLower = Base32HexNoPadLower { getBase32HexNoPadLower :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base32HexNoPadLower where isCodecM = noCodecM MbBase32HexNoPadLower ---------------------------------------------------------------------------------------------------- -- Base16Upper stub ---------------------------------------------------------------------------------------------------- newtype Base32HexNoPadUpper = Base32HexNoPadUpper { getBase32HexNoPadUpper :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base32HexNoPadUpper where isCodecM = noCodecM MbBase32HexNoPadUpper ---------------------------------------------------------------------------------------------------- -- Base32HexPadLower stub ---------------------------------------------------------------------------------------------------- newtype Base32HexPadLower = Base32HexPadLower { getBase32HexPadLower :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base32HexPadLower where isCodecM = noCodecM MbBase32HexPadLower ---------------------------------------------------------------------------------------------------- -- Base32HexPadUpper stub ---------------------------------------------------------------------------------------------------- newtype Base32HexPadUpper = Base32HexPadUpper { getBase32HexPadUpper :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base32HexPadUpper where isCodecM = noCodecM MbBase32HexPadUpper ---------------------------------------------------------------------------------------------------- -- Base32NoPadLower stub ---------------------------------------------------------------------------------------------------- newtype Base32NoPadLower = Base32NoPadLower { getBase32NoPadLower :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base32NoPadLower where isCodecM = noCodecM MbBase32NoPadLower ---------------------------------------------------------------------------------------------------- -- Base32NoPadUpper stub ---------------------------------------------------------------------------------------------------- newtype Base32NoPadUpper = Base32NoPadUpper { getBase32NoPadUpper :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base32NoPadUpper where isCodecM = noCodecM MbBase32NoPadUpper ---------------------------------------------------------------------------------------------------- -- Base32PadLower stub ---------------------------------------------------------------------------------------------------- newtype Base32PadLower = Base32PadLower { getBase32PadLower :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base32PadLower where isCodecM = noCodecM MbBase32PadLower ---------------------------------------------------------------------------------------------------- -- Base32PadUpper stub ---------------------------------------------------------------------------------------------------- newtype Base32PadUpper = Base32PadUpper { getBase32PadUpper :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base32PadUpper where isCodecM = noCodecM MbBase32PadUpper ---------------------------------------------------------------------------------------------------- -- Base32z stub ---------------------------------------------------------------------------------------------------- newtype Base32z = Base32z { getBase32z :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base32z where isCodecM = noCodecM MbBase32z ---------------------------------------------------------------------------------------------------- -- Base36Lower stub ---------------------------------------------------------------------------------------------------- newtype Base36Lower = Base36Lower { getBase36Lower :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base36Lower where isCodecM = noCodecM MbBase36Lower ---------------------------------------------------------------------------------------------------- -- Base36Upper stub ---------------------------------------------------------------------------------------------------- newtype Base36Upper = Base36Upper { getBase36Upper :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base36Upper where isCodecM = noCodecM MbBase36Upper ---------------------------------------------------------------------------------------------------- -- Base58Btc stub ---------------------------------------------------------------------------------------------------- newtype Base58Btc = Base58Btc { getBase58Btc :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base58Btc where isCodecM = noCodecM MbBase58Btc ---------------------------------------------------------------------------------------------------- -- Base58Flickr stub ---------------------------------------------------------------------------------------------------- newtype Base58Flickr = Base58Flickr { getBase58Flickr :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base58Flickr where isCodecM = noCodecM MbBase58Flickr ---------------------------------------------------------------------------------------------------- -- Base64NoPad stub ---------------------------------------------------------------------------------------------------- newtype Base64NoPad = Base64NoPad { getBase64NoPad :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base64NoPad where isCodecM = noCodecM MbBase64NoPad ---------------------------------------------------------------------------------------------------- -- Base64UrlNoPad stub ---------------------------------------------------------------------------------------------------- newtype Base64UrlNoPad = Base64UrlNoPad { getBase64UrlNoPad :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base64UrlNoPad where isCodecM = noCodecM MbBase64UrlNoPad ---------------------------------------------------------------------------------------------------- -- Base64urlPad stub ---------------------------------------------------------------------------------------------------- newtype Base64urlPad = Base64urlPad { getBase64urlPad :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base64urlPad where isCodecM = noCodecM MbBase64urlPad ---------------------------------------------------------------------------------------------------- -- Proquint stub ---------------------------------------------------------------------------------------------------- newtype Proquint = Proquint { getProquint :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Proquint where isCodecM = noCodecM MbProquint ---------------------------------------------------------------------------------------------------- -- Base256Emoji stub ---------------------------------------------------------------------------------------------------- newtype Base256Emoji = Base256Emoji { getBase256Emoji :: Text } deriving stock (Generic,Show) deriving newtype (Eq,NFData,Ord) instance IsCodec Base256Emoji where isCodecM = noCodecM MbBase256Emoji