{-# OPTIONS_GHC -Wno-orphans #-}
module LawfulConversions.Relations.StringAndText where
import qualified Data.Text as Text
import LawfulConversions.Classes
import LawfulConversions.Prelude
instance IsSome String Text where
to :: Text -> String
to = Text -> String
Text.unpack
maybeFrom :: String -> Maybe Text
maybeFrom String
string =
let text :: Text
text = String -> Text
Text.pack String
string
in if String
string String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> String
Text.unpack Text
text
then Text -> Maybe Text
forall a. a -> Maybe a
Just Text
text
else Maybe Text
forall a. Maybe a
Nothing
instance IsMany String Text where
from :: String -> Text
from = String -> Text
Text.pack