module Swarm.Game.Scenario.Topography.Structure.Recognition.Log where
import Data.Aeson
import Data.List.NonEmpty (NonEmpty)
import Data.List.NonEmpty.Extra qualified as NE
import GHC.Generics (Generic)
import Servant.Docs (ToSample)
import Servant.Docs qualified as SD
import Swarm.Game.Location (Location)
import Swarm.Game.Scenario.Topography.Structure.Named (StructureName, name)
import Swarm.Game.Scenario.Topography.Structure.Recognition.Static (
OrientedStructure,
)
import Swarm.Game.Scenario.Topography.Structure.Recognition.Type
import Swarm.Game.Universe (Cosmic)
import Swarm.Language.Syntax.Direction (AbsoluteDir)
renderSharedNames :: ConsolidatedRowReferences b a -> NonEmpty StructureName
renderSharedNames :: forall b a. ConsolidatedRowReferences b a -> NonEmpty StructureName
renderSharedNames =
NonEmpty StructureName -> NonEmpty StructureName
forall a. Ord a => NonEmpty a -> NonEmpty a
NE.nubOrd (NonEmpty StructureName -> NonEmpty StructureName)
-> (ConsolidatedRowReferences b a -> NonEmpty StructureName)
-> ConsolidatedRowReferences b a
-> NonEmpty StructureName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (StructureRow b a -> StructureName)
-> NonEmpty (StructureRow b a) -> NonEmpty StructureName
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map (NamedArea b -> StructureName
forall a. NamedArea a -> StructureName
name (NamedArea b -> StructureName)
-> (StructureRow b a -> NamedArea b)
-> StructureRow b a
-> StructureName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExtractedArea b a -> NamedArea b
forall b a. ExtractedArea b a -> NamedArea b
originalItem (ExtractedArea b a -> NamedArea b)
-> (StructureRow b a -> ExtractedArea b a)
-> StructureRow b a
-> NamedArea b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StructureWithGrid b a -> ExtractedArea b a
forall b a. StructureWithGrid b a -> ExtractedArea b a
entityGrid (StructureWithGrid b a -> ExtractedArea b a)
-> (StructureRow b a -> StructureWithGrid b a)
-> StructureRow b a
-> ExtractedArea b a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StructureRow b a -> StructureWithGrid b a
forall b a. StructureRow b a -> StructureWithGrid b a
wholeStructure) (NonEmpty (StructureRow b a) -> NonEmpty StructureName)
-> (ConsolidatedRowReferences b a -> NonEmpty (StructureRow b a))
-> ConsolidatedRowReferences b a
-> NonEmpty StructureName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConsolidatedRowReferences b a -> NonEmpty (StructureRow b a)
forall b a.
ConsolidatedRowReferences b a -> NonEmpty (StructureRow b a)
referencingRows
data ParticipatingEntity e = ParticipatingEntity
{ forall e. ParticipatingEntity e -> e
entity :: e
, forall e. ParticipatingEntity e -> InspectionOffsets
searchOffsets :: InspectionOffsets
}
deriving ((forall a b.
(a -> b) -> ParticipatingEntity a -> ParticipatingEntity b)
-> (forall a b.
a -> ParticipatingEntity b -> ParticipatingEntity a)
-> Functor ParticipatingEntity
forall a b. a -> ParticipatingEntity b -> ParticipatingEntity a
forall a b.
(a -> b) -> ParticipatingEntity a -> ParticipatingEntity b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b.
(a -> b) -> ParticipatingEntity a -> ParticipatingEntity b
fmap :: forall a b.
(a -> b) -> ParticipatingEntity a -> ParticipatingEntity b
$c<$ :: forall a b. a -> ParticipatingEntity b -> ParticipatingEntity a
<$ :: forall a b. a -> ParticipatingEntity b -> ParticipatingEntity a
Functor, (forall x. ParticipatingEntity e -> Rep (ParticipatingEntity e) x)
-> (forall x.
Rep (ParticipatingEntity e) x -> ParticipatingEntity e)
-> Generic (ParticipatingEntity e)
forall x. Rep (ParticipatingEntity e) x -> ParticipatingEntity e
forall x. ParticipatingEntity e -> Rep (ParticipatingEntity e) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall e x. Rep (ParticipatingEntity e) x -> ParticipatingEntity e
forall e x. ParticipatingEntity e -> Rep (ParticipatingEntity e) x
$cfrom :: forall e x. ParticipatingEntity e -> Rep (ParticipatingEntity e) x
from :: forall x. ParticipatingEntity e -> Rep (ParticipatingEntity e) x
$cto :: forall e x. Rep (ParticipatingEntity e) x -> ParticipatingEntity e
to :: forall x. Rep (ParticipatingEntity e) x -> ParticipatingEntity e
Generic, [ParticipatingEntity e] -> Value
[ParticipatingEntity e] -> Encoding
ParticipatingEntity e -> Bool
ParticipatingEntity e -> Value
ParticipatingEntity e -> Encoding
(ParticipatingEntity e -> Value)
-> (ParticipatingEntity e -> Encoding)
-> ([ParticipatingEntity e] -> Value)
-> ([ParticipatingEntity e] -> Encoding)
-> (ParticipatingEntity e -> Bool)
-> ToJSON (ParticipatingEntity e)
forall e. ToJSON e => [ParticipatingEntity e] -> Value
forall e. ToJSON e => [ParticipatingEntity e] -> Encoding
forall e. ToJSON e => ParticipatingEntity e -> Bool
forall e. ToJSON e => ParticipatingEntity e -> Value
forall e. ToJSON e => ParticipatingEntity e -> Encoding
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: forall e. ToJSON e => ParticipatingEntity e -> Value
toJSON :: ParticipatingEntity e -> Value
$ctoEncoding :: forall e. ToJSON e => ParticipatingEntity e -> Encoding
toEncoding :: ParticipatingEntity e -> Encoding
$ctoJSONList :: forall e. ToJSON e => [ParticipatingEntity e] -> Value
toJSONList :: [ParticipatingEntity e] -> Value
$ctoEncodingList :: forall e. ToJSON e => [ParticipatingEntity e] -> Encoding
toEncodingList :: [ParticipatingEntity e] -> Encoding
$comitField :: forall e. ToJSON e => ParticipatingEntity e -> Bool
omitField :: ParticipatingEntity e -> Bool
ToJSON)
data IntactPlacementLog e = IntactPlacementLog
{ forall e.
IntactPlacementLog e -> Maybe (StructureIntactnessFailure e)
intactnessFailure :: Maybe (StructureIntactnessFailure e)
, forall e.
IntactPlacementLog e -> PositionedStructure OrientedStructure
placedStructure :: PositionedStructure OrientedStructure
}
deriving ((forall a b.
(a -> b) -> IntactPlacementLog a -> IntactPlacementLog b)
-> (forall a b. a -> IntactPlacementLog b -> IntactPlacementLog a)
-> Functor IntactPlacementLog
forall a b. a -> IntactPlacementLog b -> IntactPlacementLog a
forall a b.
(a -> b) -> IntactPlacementLog a -> IntactPlacementLog b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b.
(a -> b) -> IntactPlacementLog a -> IntactPlacementLog b
fmap :: forall a b.
(a -> b) -> IntactPlacementLog a -> IntactPlacementLog b
$c<$ :: forall a b. a -> IntactPlacementLog b -> IntactPlacementLog a
<$ :: forall a b. a -> IntactPlacementLog b -> IntactPlacementLog a
Functor, (forall x. IntactPlacementLog e -> Rep (IntactPlacementLog e) x)
-> (forall x. Rep (IntactPlacementLog e) x -> IntactPlacementLog e)
-> Generic (IntactPlacementLog e)
forall x. Rep (IntactPlacementLog e) x -> IntactPlacementLog e
forall x. IntactPlacementLog e -> Rep (IntactPlacementLog e) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall e x. Rep (IntactPlacementLog e) x -> IntactPlacementLog e
forall e x. IntactPlacementLog e -> Rep (IntactPlacementLog e) x
$cfrom :: forall e x. IntactPlacementLog e -> Rep (IntactPlacementLog e) x
from :: forall x. IntactPlacementLog e -> Rep (IntactPlacementLog e) x
$cto :: forall e x. Rep (IntactPlacementLog e) x -> IntactPlacementLog e
to :: forall x. Rep (IntactPlacementLog e) x -> IntactPlacementLog e
Generic, [IntactPlacementLog e] -> Value
[IntactPlacementLog e] -> Encoding
IntactPlacementLog e -> Bool
IntactPlacementLog e -> Value
IntactPlacementLog e -> Encoding
(IntactPlacementLog e -> Value)
-> (IntactPlacementLog e -> Encoding)
-> ([IntactPlacementLog e] -> Value)
-> ([IntactPlacementLog e] -> Encoding)
-> (IntactPlacementLog e -> Bool)
-> ToJSON (IntactPlacementLog e)
forall e. ToJSON e => [IntactPlacementLog e] -> Value
forall e. ToJSON e => [IntactPlacementLog e] -> Encoding
forall e. ToJSON e => IntactPlacementLog e -> Bool
forall e. ToJSON e => IntactPlacementLog e -> Value
forall e. ToJSON e => IntactPlacementLog e -> Encoding
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: forall e. ToJSON e => IntactPlacementLog e -> Value
toJSON :: IntactPlacementLog e -> Value
$ctoEncoding :: forall e. ToJSON e => IntactPlacementLog e -> Encoding
toEncoding :: IntactPlacementLog e -> Encoding
$ctoJSONList :: forall e. ToJSON e => [IntactPlacementLog e] -> Value
toJSONList :: [IntactPlacementLog e] -> Value
$ctoEncodingList :: forall e. ToJSON e => [IntactPlacementLog e] -> Encoding
toEncodingList :: [IntactPlacementLog e] -> Encoding
$comitField :: forall e. ToJSON e => IntactPlacementLog e -> Bool
omitField :: IntactPlacementLog e -> Bool
ToJSON)
data ChunkMatchFailureReason e
= ChunkMatchFailureReason (NonEmpty StructureName) (RowMismatchReason e)
deriving ((forall a b.
(a -> b) -> ChunkMatchFailureReason a -> ChunkMatchFailureReason b)
-> (forall a b.
a -> ChunkMatchFailureReason b -> ChunkMatchFailureReason a)
-> Functor ChunkMatchFailureReason
forall a b.
a -> ChunkMatchFailureReason b -> ChunkMatchFailureReason a
forall a b.
(a -> b) -> ChunkMatchFailureReason a -> ChunkMatchFailureReason b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b.
(a -> b) -> ChunkMatchFailureReason a -> ChunkMatchFailureReason b
fmap :: forall a b.
(a -> b) -> ChunkMatchFailureReason a -> ChunkMatchFailureReason b
$c<$ :: forall a b.
a -> ChunkMatchFailureReason b -> ChunkMatchFailureReason a
<$ :: forall a b.
a -> ChunkMatchFailureReason b -> ChunkMatchFailureReason a
Functor, (forall x.
ChunkMatchFailureReason e -> Rep (ChunkMatchFailureReason e) x)
-> (forall x.
Rep (ChunkMatchFailureReason e) x -> ChunkMatchFailureReason e)
-> Generic (ChunkMatchFailureReason e)
forall x.
Rep (ChunkMatchFailureReason e) x -> ChunkMatchFailureReason e
forall x.
ChunkMatchFailureReason e -> Rep (ChunkMatchFailureReason e) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall e x.
Rep (ChunkMatchFailureReason e) x -> ChunkMatchFailureReason e
forall e x.
ChunkMatchFailureReason e -> Rep (ChunkMatchFailureReason e) x
$cfrom :: forall e x.
ChunkMatchFailureReason e -> Rep (ChunkMatchFailureReason e) x
from :: forall x.
ChunkMatchFailureReason e -> Rep (ChunkMatchFailureReason e) x
$cto :: forall e x.
Rep (ChunkMatchFailureReason e) x -> ChunkMatchFailureReason e
to :: forall x.
Rep (ChunkMatchFailureReason e) x -> ChunkMatchFailureReason e
Generic, [ChunkMatchFailureReason e] -> Value
[ChunkMatchFailureReason e] -> Encoding
ChunkMatchFailureReason e -> Bool
ChunkMatchFailureReason e -> Value
ChunkMatchFailureReason e -> Encoding
(ChunkMatchFailureReason e -> Value)
-> (ChunkMatchFailureReason e -> Encoding)
-> ([ChunkMatchFailureReason e] -> Value)
-> ([ChunkMatchFailureReason e] -> Encoding)
-> (ChunkMatchFailureReason e -> Bool)
-> ToJSON (ChunkMatchFailureReason e)
forall e. ToJSON e => [ChunkMatchFailureReason e] -> Value
forall e. ToJSON e => [ChunkMatchFailureReason e] -> Encoding
forall e. ToJSON e => ChunkMatchFailureReason e -> Bool
forall e. ToJSON e => ChunkMatchFailureReason e -> Value
forall e. ToJSON e => ChunkMatchFailureReason e -> Encoding
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: forall e. ToJSON e => ChunkMatchFailureReason e -> Value
toJSON :: ChunkMatchFailureReason e -> Value
$ctoEncoding :: forall e. ToJSON e => ChunkMatchFailureReason e -> Encoding
toEncoding :: ChunkMatchFailureReason e -> Encoding
$ctoJSONList :: forall e. ToJSON e => [ChunkMatchFailureReason e] -> Value
toJSONList :: [ChunkMatchFailureReason e] -> Value
$ctoEncodingList :: forall e. ToJSON e => [ChunkMatchFailureReason e] -> Encoding
toEncodingList :: [ChunkMatchFailureReason e] -> Encoding
$comitField :: forall e. ToJSON e => ChunkMatchFailureReason e -> Bool
omitField :: ChunkMatchFailureReason e -> Bool
ToJSON)
data FoundChunkComparison e = FoundChunkComparison
{ forall e. FoundChunkComparison e -> [NonEmpty e]
foundChunkKeys :: [NonEmpty e]
, forall e. FoundChunkComparison e -> [NonEmpty e]
referenceChunkKeys :: [NonEmpty e]
}
deriving ((forall a b.
(a -> b) -> FoundChunkComparison a -> FoundChunkComparison b)
-> (forall a b.
a -> FoundChunkComparison b -> FoundChunkComparison a)
-> Functor FoundChunkComparison
forall a b. a -> FoundChunkComparison b -> FoundChunkComparison a
forall a b.
(a -> b) -> FoundChunkComparison a -> FoundChunkComparison b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b.
(a -> b) -> FoundChunkComparison a -> FoundChunkComparison b
fmap :: forall a b.
(a -> b) -> FoundChunkComparison a -> FoundChunkComparison b
$c<$ :: forall a b. a -> FoundChunkComparison b -> FoundChunkComparison a
<$ :: forall a b. a -> FoundChunkComparison b -> FoundChunkComparison a
Functor, (forall x.
FoundChunkComparison e -> Rep (FoundChunkComparison e) x)
-> (forall x.
Rep (FoundChunkComparison e) x -> FoundChunkComparison e)
-> Generic (FoundChunkComparison e)
forall x. Rep (FoundChunkComparison e) x -> FoundChunkComparison e
forall x. FoundChunkComparison e -> Rep (FoundChunkComparison e) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall e x.
Rep (FoundChunkComparison e) x -> FoundChunkComparison e
forall e x.
FoundChunkComparison e -> Rep (FoundChunkComparison e) x
$cfrom :: forall e x.
FoundChunkComparison e -> Rep (FoundChunkComparison e) x
from :: forall x. FoundChunkComparison e -> Rep (FoundChunkComparison e) x
$cto :: forall e x.
Rep (FoundChunkComparison e) x -> FoundChunkComparison e
to :: forall x. Rep (FoundChunkComparison e) x -> FoundChunkComparison e
Generic, [FoundChunkComparison e] -> Value
[FoundChunkComparison e] -> Encoding
FoundChunkComparison e -> Bool
FoundChunkComparison e -> Value
FoundChunkComparison e -> Encoding
(FoundChunkComparison e -> Value)
-> (FoundChunkComparison e -> Encoding)
-> ([FoundChunkComparison e] -> Value)
-> ([FoundChunkComparison e] -> Encoding)
-> (FoundChunkComparison e -> Bool)
-> ToJSON (FoundChunkComparison e)
forall e. ToJSON e => [FoundChunkComparison e] -> Value
forall e. ToJSON e => [FoundChunkComparison e] -> Encoding
forall e. ToJSON e => FoundChunkComparison e -> Bool
forall e. ToJSON e => FoundChunkComparison e -> Value
forall e. ToJSON e => FoundChunkComparison e -> Encoding
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: forall e. ToJSON e => FoundChunkComparison e -> Value
toJSON :: FoundChunkComparison e -> Value
$ctoEncoding :: forall e. ToJSON e => FoundChunkComparison e -> Encoding
toEncoding :: FoundChunkComparison e -> Encoding
$ctoJSONList :: forall e. ToJSON e => [FoundChunkComparison e] -> Value
toJSONList :: [FoundChunkComparison e] -> Value
$ctoEncodingList :: forall e. ToJSON e => [FoundChunkComparison e] -> Encoding
toEncodingList :: [FoundChunkComparison e] -> Encoding
$comitField :: forall e. ToJSON e => FoundChunkComparison e -> Bool
omitField :: FoundChunkComparison e -> Bool
ToJSON)
data RowMismatchReason e
= NoKeysSubset (FoundChunkComparison e)
|
EmptyIntersection
deriving ((forall a b.
(a -> b) -> RowMismatchReason a -> RowMismatchReason b)
-> (forall a b. a -> RowMismatchReason b -> RowMismatchReason a)
-> Functor RowMismatchReason
forall a b. a -> RowMismatchReason b -> RowMismatchReason a
forall a b. (a -> b) -> RowMismatchReason a -> RowMismatchReason b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> RowMismatchReason a -> RowMismatchReason b
fmap :: forall a b. (a -> b) -> RowMismatchReason a -> RowMismatchReason b
$c<$ :: forall a b. a -> RowMismatchReason b -> RowMismatchReason a
<$ :: forall a b. a -> RowMismatchReason b -> RowMismatchReason a
Functor, (forall x. RowMismatchReason e -> Rep (RowMismatchReason e) x)
-> (forall x. Rep (RowMismatchReason e) x -> RowMismatchReason e)
-> Generic (RowMismatchReason e)
forall x. Rep (RowMismatchReason e) x -> RowMismatchReason e
forall x. RowMismatchReason e -> Rep (RowMismatchReason e) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall e x. Rep (RowMismatchReason e) x -> RowMismatchReason e
forall e x. RowMismatchReason e -> Rep (RowMismatchReason e) x
$cfrom :: forall e x. RowMismatchReason e -> Rep (RowMismatchReason e) x
from :: forall x. RowMismatchReason e -> Rep (RowMismatchReason e) x
$cto :: forall e x. Rep (RowMismatchReason e) x -> RowMismatchReason e
to :: forall x. Rep (RowMismatchReason e) x -> RowMismatchReason e
Generic, [RowMismatchReason e] -> Value
[RowMismatchReason e] -> Encoding
RowMismatchReason e -> Bool
RowMismatchReason e -> Value
RowMismatchReason e -> Encoding
(RowMismatchReason e -> Value)
-> (RowMismatchReason e -> Encoding)
-> ([RowMismatchReason e] -> Value)
-> ([RowMismatchReason e] -> Encoding)
-> (RowMismatchReason e -> Bool)
-> ToJSON (RowMismatchReason e)
forall e. ToJSON e => [RowMismatchReason e] -> Value
forall e. ToJSON e => [RowMismatchReason e] -> Encoding
forall e. ToJSON e => RowMismatchReason e -> Bool
forall e. ToJSON e => RowMismatchReason e -> Value
forall e. ToJSON e => RowMismatchReason e -> Encoding
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: forall e. ToJSON e => RowMismatchReason e -> Value
toJSON :: RowMismatchReason e -> Value
$ctoEncoding :: forall e. ToJSON e => RowMismatchReason e -> Encoding
toEncoding :: RowMismatchReason e -> Encoding
$ctoJSONList :: forall e. ToJSON e => [RowMismatchReason e] -> Value
toJSONList :: [RowMismatchReason e] -> Value
$ctoEncodingList :: forall e. ToJSON e => [RowMismatchReason e] -> Encoding
toEncodingList :: [RowMismatchReason e] -> Encoding
$comitField :: forall e. ToJSON e => RowMismatchReason e -> Bool
omitField :: RowMismatchReason e -> Bool
ToJSON)
data SearchLog e
= IntactStaticPlacement [IntactPlacementLog e]
| StartSearchAt (Cosmic Location) InspectionOffsets
| FoundParticipatingEntity (ParticipatingEntity e)
| FoundCompleteStructureCandidates [(OrientedStructure, Cosmic Location)]
| RecognizedSingleStructure (OrientedStructure, Cosmic Location)
|
FoundPiecewiseChunks [(NonEmpty Int, NonEmpty e)]
| ExpectedChunks (NonEmpty [NonEmpty e])
| WorldRowContent [Maybe e]
| ChunksMatchingExpected [ChunkedRowMatch (NonEmpty StructureName) e]
| ChunkFailures [ChunkMatchFailureReason e]
| ChunkIntactnessVerification (IntactPlacementLog e)
| StructureRemoved StructureName
deriving ((forall a b. (a -> b) -> SearchLog a -> SearchLog b)
-> (forall a b. a -> SearchLog b -> SearchLog a)
-> Functor SearchLog
forall a b. a -> SearchLog b -> SearchLog a
forall a b. (a -> b) -> SearchLog a -> SearchLog b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> SearchLog a -> SearchLog b
fmap :: forall a b. (a -> b) -> SearchLog a -> SearchLog b
$c<$ :: forall a b. a -> SearchLog b -> SearchLog a
<$ :: forall a b. a -> SearchLog b -> SearchLog a
Functor, (forall x. SearchLog e -> Rep (SearchLog e) x)
-> (forall x. Rep (SearchLog e) x -> SearchLog e)
-> Generic (SearchLog e)
forall x. Rep (SearchLog e) x -> SearchLog e
forall x. SearchLog e -> Rep (SearchLog e) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall e x. Rep (SearchLog e) x -> SearchLog e
forall e x. SearchLog e -> Rep (SearchLog e) x
$cfrom :: forall e x. SearchLog e -> Rep (SearchLog e) x
from :: forall x. SearchLog e -> Rep (SearchLog e) x
$cto :: forall e x. Rep (SearchLog e) x -> SearchLog e
to :: forall x. Rep (SearchLog e) x -> SearchLog e
Generic)
instance (ToJSON e) => ToJSON (SearchLog e) where
toJSON :: SearchLog e -> Value
toJSON = Options -> SearchLog e -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
searchLogOptions
searchLogOptions :: Options
searchLogOptions :: Options
searchLogOptions =
Options
defaultOptions
{ sumEncoding = ObjectWithSingleField
}
instance ToSample (SearchLog e) where
toSamples :: Proxy (SearchLog e) -> [(Text, SearchLog e)]
toSamples Proxy (SearchLog e)
_ = [(Text, SearchLog e)]
forall a. [(Text, a)]
SD.noSamples
data StructureLocation = StructureLocation StructureName (Cosmic Location, AbsoluteDir)
deriving ((forall x. StructureLocation -> Rep StructureLocation x)
-> (forall x. Rep StructureLocation x -> StructureLocation)
-> Generic StructureLocation
forall x. Rep StructureLocation x -> StructureLocation
forall x. StructureLocation -> Rep StructureLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StructureLocation -> Rep StructureLocation x
from :: forall x. StructureLocation -> Rep StructureLocation x
$cto :: forall x. Rep StructureLocation x -> StructureLocation
to :: forall x. Rep StructureLocation x -> StructureLocation
Generic, [StructureLocation] -> Value
[StructureLocation] -> Encoding
StructureLocation -> Bool
StructureLocation -> Value
StructureLocation -> Encoding
(StructureLocation -> Value)
-> (StructureLocation -> Encoding)
-> ([StructureLocation] -> Value)
-> ([StructureLocation] -> Encoding)
-> (StructureLocation -> Bool)
-> ToJSON StructureLocation
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: StructureLocation -> Value
toJSON :: StructureLocation -> Value
$ctoEncoding :: StructureLocation -> Encoding
toEncoding :: StructureLocation -> Encoding
$ctoJSONList :: [StructureLocation] -> Value
toJSONList :: [StructureLocation] -> Value
$ctoEncodingList :: [StructureLocation] -> Encoding
toEncodingList :: [StructureLocation] -> Encoding
$comitField :: StructureLocation -> Bool
omitField :: StructureLocation -> Bool
ToJSON)
instance ToSample StructureLocation where
toSamples :: Proxy StructureLocation -> [(Text, StructureLocation)]
toSamples Proxy StructureLocation
_ = [(Text, StructureLocation)]
forall a. [(Text, a)]
SD.noSamples