{-# 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 DataKinds #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeSynonymInstances #-} module Data.Multibase.Types.Internal.IsConvertible where import Data.Text.Encoding as TE import Data.Text.Lazy.Encoding as TEL import qualified Data.Text.Short as ST import Data.Multibase.Types.Internal.Basic class IsConvertible a a' where convertText :: a -> a' summarizeTextInput :: a -> a' -> Maybe Text summarizeTextInput = const $ const Nothing instance IsConvertible ByteString ByteString where convertText = id instance IsConvertible ByteStringLazy ByteStringLazy where convertText = id instance IsConvertible ByteStringShort ByteStringShort where convertText = id instance IsConvertible Text Text where convertText = id instance IsConvertible TextLazy TextLazy where convertText = id instance IsConvertible TextShort TextShort where convertText = id instance IsConvertible Text ByteString where convertText = TE.encodeUtf8 instance IsConvertible TextLazy ByteStringLazy where convertText = TEL.encodeUtf8 instance IsConvertible TextShort ByteStringShort where convertText = ST.toShortByteString