{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} module Codec.Xlsx.Types.Internal where import Control.Arrow import Data.Monoid ((<>)) import Data.Text (Text) import GHC.Generics (Generic) import Codec.Xlsx.Parser.Internal import Codec.Xlsx.Writer.Internal newtype RefId = RefId { RefId -> Text unRefId :: Text } deriving (RefId -> RefId -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: RefId -> RefId -> Bool $c/= :: RefId -> RefId -> Bool == :: RefId -> RefId -> Bool $c== :: RefId -> RefId -> Bool Eq, Eq RefId RefId -> RefId -> Bool RefId -> RefId -> Ordering RefId -> RefId -> RefId forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: RefId -> RefId -> RefId $cmin :: RefId -> RefId -> RefId max :: RefId -> RefId -> RefId $cmax :: RefId -> RefId -> RefId >= :: RefId -> RefId -> Bool $c>= :: RefId -> RefId -> Bool > :: RefId -> RefId -> Bool $c> :: RefId -> RefId -> Bool <= :: RefId -> RefId -> Bool $c<= :: RefId -> RefId -> Bool < :: RefId -> RefId -> Bool $c< :: RefId -> RefId -> Bool compare :: RefId -> RefId -> Ordering $ccompare :: RefId -> RefId -> Ordering Ord, Int -> RefId -> ShowS [RefId] -> ShowS RefId -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [RefId] -> ShowS $cshowList :: [RefId] -> ShowS show :: RefId -> String $cshow :: RefId -> String showsPrec :: Int -> RefId -> ShowS $cshowsPrec :: Int -> RefId -> ShowS Show, forall x. Rep RefId x -> RefId forall x. RefId -> Rep RefId x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep RefId x -> RefId $cfrom :: forall x. RefId -> Rep RefId x Generic) instance ToAttrVal RefId where toAttrVal :: RefId -> Text toAttrVal = forall a. ToAttrVal a => a -> Text toAttrVal forall b c a. (b -> c) -> (a -> b) -> a -> c . RefId -> Text unRefId instance FromAttrVal RefId where fromAttrVal :: Reader RefId fromAttrVal Text t = forall (a :: * -> * -> *) b c d. Arrow a => a b c -> a (b, d) (c, d) first Text -> RefId RefId forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> forall a. FromAttrVal a => Reader a fromAttrVal Text t instance FromAttrBs RefId where fromAttrBs :: ByteString -> Either Text RefId fromAttrBs = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap Text -> RefId RefId forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. FromAttrBs a => ByteString -> Either Text a fromAttrBs unsafeRefId :: Int -> RefId unsafeRefId :: Int -> RefId unsafeRefId Int num = Text -> RefId RefId forall a b. (a -> b) -> a -> b $ Text "rId" forall a. Semigroup a => a -> a -> a <> forall a. Integral a => a -> Text txti Int num