{-# OPTIONS_GHC -fno-warn-orphans #-} module Data.Binary.Instances.CaseInsensitive where import Data.Binary (Binary, get, put) import Data.Binary.Orphans () import qualified Data.CaseInsensitive as CI instance (CI.FoldCase a, Binary a) => Binary (CI.CI a) where get :: Get (CI a) get = (a -> CI a) -> Get a -> Get (CI a) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap a -> CI a forall s. FoldCase s => s -> CI s CI.mk Get a forall t. Binary t => Get t get put :: CI a -> Put put = a -> Put forall t. Binary t => t -> Put put (a -> Put) -> (CI a -> a) -> CI a -> Put forall b c a. (b -> c) -> (a -> b) -> a -> c . CI a -> a forall s. CI s -> s CI.foldedCase