{-# 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 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall s. FoldCase s => s -> CI s
CI.mk forall t. Binary t => Get t
get
    put :: CI a -> Put
put = forall t. Binary t => t -> Put
put forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. CI s -> s
CI.foldedCase