module Chiasma.Data.Ident where

import Data.Data (Data)
import Data.UUID (UUID)
import qualified Data.UUID as UUID (fromText, toText)
import Prettyprinter (Pretty (..))
import System.Random (randomIO)

data Ident =
  Str Text
  |
  Uuid UUID
  deriving stock (Ident -> Ident -> Bool
(Ident -> Ident -> Bool) -> (Ident -> Ident -> Bool) -> Eq Ident
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Ident -> Ident -> Bool
== :: Ident -> Ident -> Bool
$c/= :: Ident -> Ident -> Bool
/= :: Ident -> Ident -> Bool
Eq, Int -> Ident -> ShowS
[Ident] -> ShowS
Ident -> String
(Int -> Ident -> ShowS)
-> (Ident -> String) -> ([Ident] -> ShowS) -> Show Ident
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Ident -> ShowS
showsPrec :: Int -> Ident -> ShowS
$cshow :: Ident -> String
show :: Ident -> String
$cshowList :: [Ident] -> ShowS
showList :: [Ident] -> ShowS
Show, Eq Ident
Eq Ident
-> (Ident -> Ident -> Ordering)
-> (Ident -> Ident -> Bool)
-> (Ident -> Ident -> Bool)
-> (Ident -> Ident -> Bool)
-> (Ident -> Ident -> Bool)
-> (Ident -> Ident -> Ident)
-> (Ident -> Ident -> Ident)
-> Ord Ident
Ident -> Ident -> Bool
Ident -> Ident -> Ordering
Ident -> Ident -> Ident
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
$ccompare :: Ident -> Ident -> Ordering
compare :: Ident -> Ident -> Ordering
$c< :: Ident -> Ident -> Bool
< :: Ident -> Ident -> Bool
$c<= :: Ident -> Ident -> Bool
<= :: Ident -> Ident -> Bool
$c> :: Ident -> Ident -> Bool
> :: Ident -> Ident -> Bool
$c>= :: Ident -> Ident -> Bool
>= :: Ident -> Ident -> Bool
$cmax :: Ident -> Ident -> Ident
max :: Ident -> Ident -> Ident
$cmin :: Ident -> Ident -> Ident
min :: Ident -> Ident -> Ident
Ord, (forall x. Ident -> Rep Ident x)
-> (forall x. Rep Ident x -> Ident) -> Generic Ident
forall x. Rep Ident x -> Ident
forall x. Ident -> Rep Ident x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Ident -> Rep Ident x
from :: forall x. Ident -> Rep Ident x
$cto :: forall x. Rep Ident x -> Ident
to :: forall x. Rep Ident x -> Ident
Generic, Typeable Ident
Typeable Ident
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Ident -> c Ident)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Ident)
-> (Ident -> Constr)
-> (Ident -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Ident))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident))
-> ((forall b. Data b => b -> b) -> Ident -> Ident)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r)
-> (forall u. (forall d. Data d => d -> u) -> Ident -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Ident -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Ident -> m Ident)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Ident -> m Ident)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Ident -> m Ident)
-> Data Ident
Ident -> Constr
Ident -> DataType
(forall b. Data b => b -> b) -> Ident -> Ident
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Ident -> u
forall u. (forall d. Data d => d -> u) -> Ident -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Ident -> m Ident
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Ident -> m Ident
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Ident
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Ident -> c Ident
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Ident)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Ident -> c Ident
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Ident -> c Ident
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Ident
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Ident
$ctoConstr :: Ident -> Constr
toConstr :: Ident -> Constr
$cdataTypeOf :: Ident -> DataType
dataTypeOf :: Ident -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Ident)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Ident)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident)
$cgmapT :: (forall b. Data b => b -> b) -> Ident -> Ident
gmapT :: (forall b. Data b => b -> b) -> Ident -> Ident
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Ident -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Ident -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Ident -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Ident -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Ident -> m Ident
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Ident -> m Ident
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Ident -> m Ident
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Ident -> m Ident
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Ident -> m Ident
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Ident -> m Ident
Data)

json ''Ident

class Identifiable a where
  identify :: a -> Ident

instance Identifiable Ident where
  identify :: Ident -> Ident
identify = Ident -> Ident
forall a. a -> a
id

instance Pretty Ident where
  pretty :: forall ann. Ident -> Doc ann
pretty =
    Text -> Doc ann
forall ann. Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Text -> Doc ann) -> (Ident -> Text) -> Ident -> Doc ann
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
      Str Text
s -> Text
s
      Uuid UUID
u -> UUID -> Text
UUID.toText UUID
u

instance Default Ident where
  def :: Ident
def =
    Text -> Ident
Str Text
""

instance IsString Ident where
  fromString :: String -> Ident
fromString =
    Text -> Ident
Str (Text -> Ident) -> (String -> Text) -> String -> Ident
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. ToText a => a -> Text
toText

sameIdent ::
  Identifiable a =>
  Identifiable b =>
  a ->
  b ->
  Bool
sameIdent :: forall a b. (Identifiable a, Identifiable b) => a -> b -> Bool
sameIdent a
target b
b =
  a -> Ident
forall a. Identifiable a => a -> Ident
identify a
target Ident -> Ident -> Bool
forall a. Eq a => a -> a -> Bool
== b -> Ident
forall a. Identifiable a => a -> Ident
identify b
b

identText :: Ident -> Text
identText :: Ident -> Text
identText (Str Text
a) = Text
a
identText (Uuid UUID
a) = UUID -> Text
UUID.toText UUID
a

generateIdent :: MonadIO m => m Ident
generateIdent :: forall (m :: * -> *). MonadIO m => m Ident
generateIdent = IO Ident -> m Ident
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Ident -> m Ident) -> IO Ident -> m Ident
forall a b. (a -> b) -> a -> b
$ UUID -> Ident
Uuid (UUID -> Ident) -> IO UUID -> IO Ident
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO UUID
forall a (m :: * -> *). (Random a, MonadIO m) => m a
randomIO

parseIdent :: Text -> Ident
parseIdent :: Text -> Ident
parseIdent Text
text =
  Ident -> (UUID -> Ident) -> Maybe UUID -> Ident
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Text -> Ident
Str Text
text) UUID -> Ident
Uuid (Text -> Maybe UUID
UUID.fromText Text
text)