{-# LANGUAGE QuasiQuotes, ScopedTypeVariables, OverloadedStrings #-} {-# LANGUAGE PackageImports #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE DerivingStrategies #-} import qualified Data.Text as T import qualified Data.Text.Lazy as LT import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as LB import qualified Data.ByteString.Builder as LB import Data.Foldable ( foldMap ) import "quickcheck-text" Data.Text.Arbitrary import "hspec" Test.Hspec import "QuickCheck" Test.QuickCheck import "quickcheck-instances" Test.QuickCheck.Instances.ByteString import "string-interpolate" Data.String.Interpolate ( i ) main :: IO () main = hspec $ parallel $ do describe "i" $ do context "when using String as a parameter" $ do it "just interpolating should be id" $ property $ \(str :: String) -> [i|#{str}|] == str it "should passthrough a conversion to strict Text and back unchanged" $ property $ \(str :: String) -> let t = [i|#{str}|] :: T.Text str' = [i|#{t}|] :: String in str' == str it "should passthrough a conversion to lazy Text and back unchanged" $ property $ \(str :: String) -> let lt = [i|#{str}|] :: LT.Text str' = [i|#{lt}|] :: String in str' == str it "should passthrough a conversion to strict ByteString and back unchanged" $ property $ \(str :: String) -> let b = [i|#{str}|] :: B.ByteString str' = [i|#{b}|] :: String in str' == str it "should passthrough a conversion to lazy ByteString and back unchanged" $ property $ \(str :: String) -> let lb = [i|#{str}|] :: LB.ByteString str' = [i|#{lb}|] :: String in str' == str context "when using strict Text as a parameter" $ do it "just interpolating should be id" $ property $ \(t :: T.Text) -> [i|#{t}|] == t it "should passthrough a conversion to String and back unchanged" $ property $ \(t :: T.Text) -> let str = [i|#{t}|] :: String t' = [i|#{str}|] :: T.Text in t' == t it "should passthrough a conversion to lazy Text and back unchanged" $ property $ \(t :: T.Text) -> let lt = [i|#{t}|] :: LT.Text t' = [i|#{lt}|] :: T.Text in t' == t it "should passthrough a conversion to strict ByteString and back unchanged" $ property $ \(t :: T.Text) -> let b = [i|#{t}|] :: B.ByteString t' = [i|#{b}|] :: T.Text in t' == t it "should passthrough a conversion to lazy ByteString and back unchanged" $ property $ \(t :: T.Text) -> let lb = [i|#{t}|] :: LB.ByteString t' = [i|#{lb}|] :: T.Text in t' == t context "when using lazy Text as a parameter" $ do it "just interpolating should be id" $ property $ \(lt :: LT.Text) -> [i|#{lt}|] == lt it "should passthrough a conversion to String and back unchanged" $ property $ \(lt :: LT.Text) -> let str = [i|#{lt}|] :: String lt' = [i|#{str}|] :: LT.Text in lt' == lt it "should passthrough a conversion to strict Text and back unchanged" $ property $ \(lt :: LT.Text) -> let t = [i|#{lt}|] :: T.Text lt' = [i|#{t}|] :: LT.Text in lt' == lt it "should passthrough a conversion to strict ByteString and back unchanged" $ property $ \(lt :: LT.Text) -> let b = [i|#{lt}|] :: B.ByteString lt' = [i|#{b}|] :: LT.Text in lt' == lt it "should passthrough a conversion to lazy ByteString and back unchanged" $ property $ \(lt :: LT.Text) -> let lb = [i|#{lt}|] :: LB.ByteString lt' = [i|#{lb}|] :: LT.Text in lt' == lt context "when using strict ByteString as a parameter" $ do it "just interpolating should be id" $ property $ \(b :: B.ByteString) -> [i|#{b}|] == b it "should passthrough a conversion to lazy ByteString and back unchanged" $ property $ \(b :: B.ByteString) -> let lb = [i|#{b}|] :: LB.ByteString b' = [i|#{lb}|] :: B.ByteString in b' == b context "and the ByteString is valid UTF8" $ do it "should passthrough a conversion to String and back unchanged" $ do property $ \(UTF8 b) -> let str = [i|#{b}|] :: String b' = [i|#{str}|] in b' == b it "should passthrough a conversion to strict Text and back unchanged" $ do property $ \(UTF8 b) -> let t = [i|#{b}|] :: T.Text b' = [i|#{t}|] in b' == b it "should passthrough a conversion to lazy Text and back unchanged" $ do property $ \(UTF8 b) -> let lt = [i|#{b}|] :: LT.Text b' = [i|#{lt}|] in b' == b context "when using lazy ByteString as a parameter" $ do it "just interpolating should be id" $ property $ \(lb :: LB.ByteString) -> [i|#{lb}|] == lb it "should passthrough a conversion to strict ByteString and back unchanged" $ property $ \(lb :: LB.ByteString) -> let b = [i|#{lb}|] :: B.ByteString lb' = [i|#{b}|] :: LB.ByteString in lb' == lb context "and the ByteString is valid UTF8" $ do it "should passthrough a conversion to String and back unchanged" $ property $ \(LUTF8 lb) -> let str = [i|#{lb}|] :: String lb' = [i|#{str}|] in lb' == lb it "should passthrough a conversion to strict Text and back unchanged" $ property $ \(LUTF8 lb) -> let t = [i|#{lb}|] :: T.Text lb' = [i|#{t}|] in lb' == lb it "should passthrough a conversion to lazy Text and back unchanged" $ property $ \(LUTF8 lb) -> let lt = [i|#{lb}|] :: LT.Text lb' = [i|#{lt}|] in lb' == lb newtype UTF8ByteString = UTF8 { unUTF8 :: B.ByteString } deriving newtype (Eq, Show) newtype LUTF8ByteString = LUTF8 { unLUTF8 :: LB.ByteString } deriving newtype (Eq, Show) instance Arbitrary LUTF8ByteString where arbitrary = LUTF8 . LB.toLazyByteString . foldMap LB.charUtf8 <$> arbitrary @[Char] instance Arbitrary UTF8ByteString where arbitrary = UTF8 . LB.toStrict . LB.toLazyByteString . foldMap LB.charUtf8 <$> arbitrary @[Char] -- Why the hell doesn't `quickcheck-text' not provide this -- instance already? I don't know. Don't ask me. instance Arbitrary LT.Text where arbitrary = LT.fromStrict <$> arbitrary shrink t = LT.fromStrict <$> shrink (LT.toStrict t)