{-# LANGUAGE TemplateHaskell #-} module Rattletrap.Type.Str ( Str(..) , toStr , fromStr ) where import Rattletrap.Type.Common import qualified Data.Text as Text newtype Str = Str { Str -> Text strValue :: Text } deriving (Str -> Str -> Bool (Str -> Str -> Bool) -> (Str -> Str -> Bool) -> Eq Str forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Str -> Str -> Bool $c/= :: Str -> Str -> Bool == :: Str -> Str -> Bool $c== :: Str -> Str -> Bool Eq, Eq Str Eq Str -> (Str -> Str -> Ordering) -> (Str -> Str -> Bool) -> (Str -> Str -> Bool) -> (Str -> Str -> Bool) -> (Str -> Str -> Bool) -> (Str -> Str -> Str) -> (Str -> Str -> Str) -> Ord Str Str -> Str -> Bool Str -> Str -> Ordering Str -> Str -> Str 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 :: Str -> Str -> Str $cmin :: Str -> Str -> Str max :: Str -> Str -> Str $cmax :: Str -> Str -> Str >= :: Str -> Str -> Bool $c>= :: Str -> Str -> Bool > :: Str -> Str -> Bool $c> :: Str -> Str -> Bool <= :: Str -> Str -> Bool $c<= :: Str -> Str -> Bool < :: Str -> Str -> Bool $c< :: Str -> Str -> Bool compare :: Str -> Str -> Ordering $ccompare :: Str -> Str -> Ordering $cp1Ord :: Eq Str Ord, Int -> Str -> ShowS [Str] -> ShowS Str -> String (Int -> Str -> ShowS) -> (Str -> String) -> ([Str] -> ShowS) -> Show Str forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Str] -> ShowS $cshowList :: [Str] -> ShowS show :: Str -> String $cshow :: Str -> String showsPrec :: Int -> Str -> ShowS $cshowsPrec :: Int -> Str -> ShowS Show) $(deriveJson ''Str) toStr :: String -> Str toStr :: String -> Str toStr String string = Text -> Str Str (String -> Text Text.pack String string) fromStr :: Str -> String fromStr :: Str -> String fromStr Str text = Text -> String Text.unpack (Str -> Text strValue Str text)