{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE OverloadedStrings #-}
module Database.EventStore.Internal.Stream where
import Database.EventStore.Internal.Prelude
import Database.EventStore.Internal.Types
data StreamId loc where
StreamName :: Text -> StreamId EventNumber
All :: StreamId Position
isAllStream :: StreamId t -> Bool
isAllStream :: forall t. StreamId t -> Bool
isAllStream StreamName{} = Bool
False
isAllStream StreamId t
_ = Bool
True
instance Eq (StreamId t) where
StreamName Text
n == :: StreamId t -> StreamId t -> Bool
== StreamName Text
v = Text
n forall a. Eq a => a -> a -> Bool
== Text
v
StreamId t
All == StreamId t
_ = Bool
True
type StreamName = StreamId EventNumber
streamIdRaw :: StreamId t -> Text
streamIdRaw :: forall t. StreamId t -> Text
streamIdRaw (StreamName Text
n) = Text
n
streamIdRaw StreamId t
All = Text
""
instance Show (StreamId t) where
show :: StreamId t -> String
show (StreamName Text
n) = forall a. Show a => a -> String
show Text
n
show StreamId t
All = String
"$all"