{-# LANGUAGE CPP              #-}
{-# LANGUAGE FlexibleContexts #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Test.QuickCheck.Instances.Text.Short () where

import Prelude ()
import Test.QuickCheck.Instances.CustomPrelude

import Test.QuickCheck

import qualified Data.Text.Short as T

-------------------------------------------------------------------------------
-- text
-------------------------------------------------------------------------------

instance Arbitrary T.ShortText where
    arbitrary :: Gen ShortText
arbitrary = [Char] -> ShortText
T.pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
    shrink :: ShortText -> [ShortText]
shrink ShortText
xs = [Char] -> ShortText
T.pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => a -> [a]
shrink (ShortText -> [Char]
T.unpack ShortText
xs)

instance CoArbitrary T.ShortText where
    coarbitrary :: forall b. ShortText -> Gen b -> Gen b
coarbitrary = forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> [Char]
T.unpack

instance Function T.ShortText where
    function :: forall b. (ShortText -> b) -> ShortText :-> b
function = forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap ShortText -> [Char]
T.unpack [Char] -> ShortText
T.pack