gtvm-hs-1.0.0: Various tools for reversing and using assets from Golden Time: Vivid Memories.
Safe HaskellNone
LanguageGHC2021

GTVM.SCP

Description

Definitions for the SCP schema used in Golden Time: Vivid Memories.

This module doubles as a sort of showcase for raehik's zoo of high-performance binary and generics libraries, and how one might use them to do some reverse engineering.

The Seg type and definitions following it are of primary interest.

Synopsis

Documentation

type W8 = Word8 Source #

Shorthand for a single byte.

type W32 = ByteOrdered 'LittleEndian Word32 Source #

Shorthand for a little-endian 4-byte word. (The SCP format solely uses little-endian, so we simply hard-code it here.)

type PfxLenW8 = CountPrefixed Word8 [] Source #

Shorthand for a list of something, prefixed by its length as a single byte.

newtype AW32Pairs (s :: Strength) a Source #

Constructors

AW32Pairs 

Fields

Instances

Instances details
Functor (AW32Pairs 'Weak) Source # 
Instance details

Defined in GTVM.SCP

Methods

fmap :: (a -> b) -> AW32Pairs 'Weak a -> AW32Pairs 'Weak b #

(<$) :: a -> AW32Pairs 'Weak b -> AW32Pairs 'Weak a #

Foldable (AW32Pairs 'Weak) Source # 
Instance details

Defined in GTVM.SCP

Methods

fold :: Monoid m => AW32Pairs 'Weak m -> m #

foldMap :: Monoid m => (a -> m) -> AW32Pairs 'Weak a -> m #

foldMap' :: Monoid m => (a -> m) -> AW32Pairs 'Weak a -> m #

foldr :: (a -> b -> b) -> b -> AW32Pairs 'Weak a -> b #

foldr' :: (a -> b -> b) -> b -> AW32Pairs 'Weak a -> b #

foldl :: (b -> a -> b) -> b -> AW32Pairs 'Weak a -> b #

foldl' :: (b -> a -> b) -> b -> AW32Pairs 'Weak a -> b #

foldr1 :: (a -> a -> a) -> AW32Pairs 'Weak a -> a #

foldl1 :: (a -> a -> a) -> AW32Pairs 'Weak a -> a #

toList :: AW32Pairs 'Weak a -> [a] #

null :: AW32Pairs 'Weak a -> Bool #

length :: AW32Pairs 'Weak a -> Int #

elem :: Eq a => a -> AW32Pairs 'Weak a -> Bool #

maximum :: Ord a => AW32Pairs 'Weak a -> a #

minimum :: Ord a => AW32Pairs 'Weak a -> a #

sum :: Num a => AW32Pairs 'Weak a -> a #

product :: Num a => AW32Pairs 'Weak a -> a #

Traversable (AW32Pairs 'Weak) Source # 
Instance details

Defined in GTVM.SCP

Methods

traverse :: Applicative f => (a -> f b) -> AW32Pairs 'Weak a -> f (AW32Pairs 'Weak b) #

sequenceA :: Applicative f => AW32Pairs 'Weak (f a) -> f (AW32Pairs 'Weak a) #

mapM :: Monad m => (a -> m b) -> AW32Pairs 'Weak a -> m (AW32Pairs 'Weak b) #

sequence :: Monad m => AW32Pairs 'Weak (m a) -> m (AW32Pairs 'Weak a) #

FromJSON a => FromJSON (AW32Pairs 'Weak a) Source # 
Instance details

Defined in GTVM.SCP

ToJSON a => ToJSON (AW32Pairs 'Weak a) Source # 
Instance details

Defined in GTVM.SCP

BLen a => BLen (AW32Pairs 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Methods

blen :: AW32Pairs 'Strong a -> Int #

Get a => Get (AW32Pairs 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Methods

get :: Getter (AW32Pairs 'Strong a) #

Put a => Put (AW32Pairs 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Methods

put :: AW32Pairs 'Strong a -> Putter #

Generic (AW32Pairs s a) Source # 
Instance details

Defined in GTVM.SCP

Associated Types

type Rep (AW32Pairs s a) 
Instance details

Defined in GTVM.SCP

type Rep (AW32Pairs s a) = D1 ('MetaData "AW32Pairs" "GTVM.SCP" "gtvm-hs-1.0.0-inplace" 'True) (C1 ('MetaCons "AW32Pairs" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAW32Pairs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s (PfxLenW8 (a, SW s W32))))))

Methods

from :: AW32Pairs s a -> Rep (AW32Pairs s a) x #

to :: Rep (AW32Pairs s a) x -> AW32Pairs s a #

Show a => Show (AW32Pairs 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Show a => Show (AW32Pairs 'Weak a) Source # 
Instance details

Defined in GTVM.SCP

Eq a => Eq (AW32Pairs 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Eq a => Eq (AW32Pairs 'Weak a) Source # 
Instance details

Defined in GTVM.SCP

Methods

(==) :: AW32Pairs 'Weak a -> AW32Pairs 'Weak a -> Bool #

(/=) :: AW32Pairs 'Weak a -> AW32Pairs 'Weak a -> Bool #

Strengthen (AW32Pairs 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Weaken (AW32Pairs 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Associated Types

type Weak (AW32Pairs 'Strong a) 
Instance details

Defined in GTVM.SCP

type Rep (AW32Pairs s a) Source # 
Instance details

Defined in GTVM.SCP

type Rep (AW32Pairs s a) = D1 ('MetaData "AW32Pairs" "GTVM.SCP" "gtvm-hs-1.0.0-inplace" 'True) (C1 ('MetaCons "AW32Pairs" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAW32Pairs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s (PfxLenW8 (a, SW s W32))))))
type Weak (AW32Pairs 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

traverseFst :: Applicative f => (a -> f b) -> (a, x) -> f (b, x) Source #

newtype W322Block (s :: Strength) Source #

Constructors

W322Block 

Fields

Instances

Instances details
FromJSON (W322Block 'Weak) Source # 
Instance details

Defined in GTVM.SCP

ToJSON (W322Block 'Weak) Source # 
Instance details

Defined in GTVM.SCP

BLen (W322Block 'Strong) Source # 
Instance details

Defined in GTVM.SCP

Methods

blen :: W322Block 'Strong -> Int #

Get (W322Block 'Strong) Source # 
Instance details

Defined in GTVM.SCP

Methods

get :: Getter (W322Block 'Strong) #

Put (W322Block 'Strong) Source # 
Instance details

Defined in GTVM.SCP

Methods

put :: W322Block 'Strong -> Putter #

Generic (W322Block s) Source # 
Instance details

Defined in GTVM.SCP

Associated Types

type Rep (W322Block s) 
Instance details

Defined in GTVM.SCP

type Rep (W322Block s) = D1 ('MetaData "W322Block" "GTVM.SCP" "gtvm-hs-1.0.0-inplace" 'True) (C1 ('MetaCons "W322Block" 'PrefixI 'True) (S1 ('MetaSel ('Just "unW322Block") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s (PfxLenW8 (SW s (PfxLenW8 (SW s W32))))))))

Methods

from :: W322Block s -> Rep (W322Block s) x #

to :: Rep (W322Block s) x -> W322Block s #

Show (W322Block 'Strong) Source # 
Instance details

Defined in GTVM.SCP

Show (W322Block 'Weak) Source # 
Instance details

Defined in GTVM.SCP

Eq (W322Block 'Strong) Source # 
Instance details

Defined in GTVM.SCP

Eq (W322Block 'Weak) Source # 
Instance details

Defined in GTVM.SCP

Strengthen (W322Block 'Strong) Source # 
Instance details

Defined in GTVM.SCP

Weaken (W322Block 'Strong) Source # 
Instance details

Defined in GTVM.SCP

Associated Types

type Weak (W322Block 'Strong) 
Instance details

Defined in GTVM.SCP

type Rep (W322Block s) Source # 
Instance details

Defined in GTVM.SCP

type Rep (W322Block s) = D1 ('MetaData "W322Block" "GTVM.SCP" "gtvm-hs-1.0.0-inplace" 'True) (C1 ('MetaCons "W322Block" 'PrefixI 'True) (S1 ('MetaSel ('Just "unW322Block") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s (PfxLenW8 (SW s (PfxLenW8 (SW s W32))))))))
type Weak (W322Block 'Strong) Source # 
Instance details

Defined in GTVM.SCP

data Seg05Text (s :: Strength) a Source #

Instances

Instances details
Functor (Seg05Text 'Weak) Source # 
Instance details

Defined in GTVM.SCP

Methods

fmap :: (a -> b) -> Seg05Text 'Weak a -> Seg05Text 'Weak b #

(<$) :: a -> Seg05Text 'Weak b -> Seg05Text 'Weak a #

Foldable (Seg05Text 'Weak) Source # 
Instance details

Defined in GTVM.SCP

Methods

fold :: Monoid m => Seg05Text 'Weak m -> m #

foldMap :: Monoid m => (a -> m) -> Seg05Text 'Weak a -> m #

foldMap' :: Monoid m => (a -> m) -> Seg05Text 'Weak a -> m #

foldr :: (a -> b -> b) -> b -> Seg05Text 'Weak a -> b #

foldr' :: (a -> b -> b) -> b -> Seg05Text 'Weak a -> b #

foldl :: (b -> a -> b) -> b -> Seg05Text 'Weak a -> b #

foldl' :: (b -> a -> b) -> b -> Seg05Text 'Weak a -> b #

foldr1 :: (a -> a -> a) -> Seg05Text 'Weak a -> a #

foldl1 :: (a -> a -> a) -> Seg05Text 'Weak a -> a #

toList :: Seg05Text 'Weak a -> [a] #

null :: Seg05Text 'Weak a -> Bool #

length :: Seg05Text 'Weak a -> Int #

elem :: Eq a => a -> Seg05Text 'Weak a -> Bool #

maximum :: Ord a => Seg05Text 'Weak a -> a #

minimum :: Ord a => Seg05Text 'Weak a -> a #

sum :: Num a => Seg05Text 'Weak a -> a #

product :: Num a => Seg05Text 'Weak a -> a #

Traversable (Seg05Text 'Weak) Source # 
Instance details

Defined in GTVM.SCP

Methods

traverse :: Applicative f => (a -> f b) -> Seg05Text 'Weak a -> f (Seg05Text 'Weak b) #

sequenceA :: Applicative f => Seg05Text 'Weak (f a) -> f (Seg05Text 'Weak a) #

mapM :: Monad m => (a -> m b) -> Seg05Text 'Weak a -> m (Seg05Text 'Weak b) #

sequence :: Monad m => Seg05Text 'Weak (m a) -> m (Seg05Text 'Weak a) #

FromJSON a => FromJSON (Seg05Text 'Weak a) Source # 
Instance details

Defined in GTVM.SCP

ToJSON a => ToJSON (Seg05Text 'Weak a) Source # 
Instance details

Defined in GTVM.SCP

BLen a => BLen (Seg05Text 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Methods

blen :: Seg05Text 'Strong a -> Int #

Get a => Get (Seg05Text 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Methods

get :: Getter (Seg05Text 'Strong a) #

Put a => Put (Seg05Text 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Methods

put :: Seg05Text 'Strong a -> Putter #

Generic (Seg05Text s a) Source # 
Instance details

Defined in GTVM.SCP

Associated Types

type Rep (Seg05Text s a) 
Instance details

Defined in GTVM.SCP

type Rep (Seg05Text s a) = D1 ('MetaData "Seg05Text" "GTVM.SCP" "gtvm-hs-1.0.0-inplace" 'False) (C1 ('MetaCons "Seg05Text" 'PrefixI 'True) ((S1 ('MetaSel ('Just "seg05TextSpeakerUnkCharID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Just "seg05TextSpeakerID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :*: (S1 ('MetaSel ('Just "seg05TextText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "seg05TextVoiceLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "seg05TextCounter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))))))

Methods

from :: Seg05Text s a -> Rep (Seg05Text s a) x #

to :: Rep (Seg05Text s a) x -> Seg05Text s a #

Show a => Show (Seg05Text 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Show a => Show (Seg05Text 'Weak a) Source # 
Instance details

Defined in GTVM.SCP

Eq a => Eq (Seg05Text 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Eq a => Eq (Seg05Text 'Weak a) Source # 
Instance details

Defined in GTVM.SCP

Methods

(==) :: Seg05Text 'Weak a -> Seg05Text 'Weak a -> Bool #

(/=) :: Seg05Text 'Weak a -> Seg05Text 'Weak a -> Bool #

Strengthen (Seg05Text 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Weaken (Seg05Text 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Associated Types

type Weak (Seg05Text 'Strong a) 
Instance details

Defined in GTVM.SCP

type Rep (Seg05Text s a) Source # 
Instance details

Defined in GTVM.SCP

type Rep (Seg05Text s a) = D1 ('MetaData "Seg05Text" "GTVM.SCP" "gtvm-hs-1.0.0-inplace" 'False) (C1 ('MetaCons "Seg05Text" 'PrefixI 'True) ((S1 ('MetaSel ('Just "seg05TextSpeakerUnkCharID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Just "seg05TextSpeakerID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :*: (S1 ('MetaSel ('Just "seg05TextText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "seg05TextVoiceLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "seg05TextCounter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))))))
type Weak (Seg05Text 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

jcSeg05 :: Options Source #

Seg05Text JSON config.

If aeson were better, we would do this in types like binrep, but alas.

data Seg (s :: Strength) a Source #

A single SCP segment, or command.

In the binary schema, SCP segments are formed with a byte prefix, indicating what segment follows, followed by the appropriate segment contents. Further, segments are often made of individual fields, concatenated. This is extremely convenient to define using a Haskell ADT!

  • A single constructor defines a single segment type.
  • Constructors encode their segment byte prefix in their name.
  • Constructor fields indicate their contents, and field order.

binrep can use all of this information to derive generic serializers and parsers with minimal extra effort, provided that /every type used inside defines a precise binary schema/. For example, sized words like Word32 must be accompanied by an endianness.

This is great... but now our type is rather unwieldy for using in Haskell land, where endianness is irrelevant and we perhaps prefer to ignore word sizes. This is where the SW wrapper comes in. Wrap every type with extra, "unwanted" information in a SW (s :: Strength) a:

  • When s ~ Strong, a is used directly. This is the "exact" mode. Use this one for binrep instances.
  • When s ~ Weak, Weak a is used. Use this one for aeson instances, easy transformation, and generally working with in handwritten Haskell.

The strongweak package is used to determine how types are weakened. Usually it's stuff like removing newtype wrappers, turning words to Naturals (and signed words to Integers).

Furthermore, we can then derive our own weakeners and strengtheners. Provided you write the type as above, strongweak's generics simply do all the work for you. With all this, a command-line interface for coding between JSON and binary versions of the schema can be written in like 5 lines. (Really. See Tool.SCP.Code.)

Constructors

Seg00 
Seg01BG a (SW s W8) (SW s W8) 
Seg02SFX a (SW s W8) 
Seg03 (SW s W8) a (SW s W8) 
Seg04 (SW s W8) (SW s W8) 
Seg05 (Seg05Text s a)

Includes player-facing text.

Seg07SCP a 
Seg08 
Seg09Choice (SW s W8) (AW32Pairs s a)

Includes player-facing text. Choice selection. The W32s appear to be the same counter as textboxes!

The W8 seems to be an file-unique identifier for the choice selection. SCP files with multiple choices have 0, 1, 2 etc. in ascending order.

Seg0A (W322Block s) 
Seg0B (SW s W8) (SW s W8)

Appears to indicate where a given choice jumps to.

First W8 appears to specify which choice selection it relates to. Second W8 appears to be the choice index in that choice selection (usually 0, 1). They may be highly separated, in cases where a choice changes lots of dialog.

Seg0CFlag (SW s W8) (SW s W8) 
Seg0D (SW s W8) 
Seg0E (SW s W8) 
Seg0F 
Seg10 (SW s W8) (SW s W8) (SW s W8) 
Seg11EventCG a 
Seg12 
Seg13 (SW s W8) a (SW s W8) (SW s W32)

Possibly player-facing text. Registers words for the feast Danganronpa-style minigame, but using indices which correspond to textures with the text on. The usage of the text here is unknown.

Seg14 (SW s W8) 
Seg15 
Seg16Wadai 
Seg17 (SW s W8) (SW s W8) 
Seg18 (SW s W8) (SW s W8) 
Seg19 (SW s W8) (SW s W8) 
Seg1D 
Seg1E (SW s W8) 
Seg1FDelay 
Seg20 (SW s W8) 
Seg21 
Seg22 a (AW32Pairs s a)

Includes player-facing text. Choice, plus an extra string. Seem to be used in the conversation events.

Seg23SFX 
Seg24 a

Unknown. Text seems to correspond to MDL files in the r2d directory.

Seg25 
Seg26 
Seg27 a (SW s W8) (SW s W8)

Unknown. Text seems to correspond to MDL files in the r2d directory.

Seg28 a (SW s W8) (SW s W8)

Unknown. Text seems to correspond to MDL files in the r2d directory.

Seg29 a (SW s W8) (SW s W8)

Unknown. Text seems to correspond to MDL files in the r2d directory.

Seg2A (SW s W8) (SW s W8) 
Seg2B (SW s W8) (SW s W8) (SW s W8) a (W322Block s) 
Seg2CMap 
Seg2D a (SW s W8) (SW s W8)

Unknown. Text seems to correspond to MDL files in the r2d directory.

Seg2E (SW s W8) (SW s W8) (SW s W32) (SW s W32) 
Seg2F (SW s W8) 
Seg30 (SW s W8) 
Seg31 
Seg32 (SW s W32) (SW s W8) 
Seg33 (SW s W8) (SW s W8) 
Seg34 (SW s W32) 
Seg35 a

Likely player-facing. Kinda sounds like it's a type of Banri choice.

Seg36 (SW s W8) (SW s W32) 
Seg37 (SW s W8) (SW s W32) 
Seg38 (SW s W8) (SW s W32) 
Seg39 
Seg3A (SW s W8) (SW s W8) 
Seg3B (SW s W8) 
Seg3C (SW s W8) (SW s W8) 
Seg3D 
Seg3E (SW s W8) (SW s W8) 
Seg3F (SW s W8) (SW s W32) (SW s W32) 
Seg40 (SW s W8) 
Seg41 (SW s W8) (SW s W32) (SW s W32) 
Seg42 (SW s W8) 
Seg43SFX a 
Seg44SFX a 
Seg45SFX a (SW s W8) 
Seg46 (SW s W8) (SW s W8) 
Seg47 (SW s W8) (SW s W8) 
Seg48 
Seg49 
Seg4A 
Seg4B 
Seg4C a 
Seg4D 
Seg4E 
Seg4F a (SW s W8) (SW s W8)

Unknown. Text seems to correspond to MDL files in the r2d directory.

Seg50 a (SW s W8) (SW s W8)

Unknown. Text seems to correspond to MDL files in the r2d directory.

Seg51 a (SW s W8) (SW s W8)

Unknown. Text seems to correspond to MDL files in the r2d directory.

Seg52 a

Text not user-facing. Refers to a sound/voice file - all the uses I've seen are girls telling you 飲んで飲んで!

Seg53 a (SW s W8) (SW s W8)

Unknown. Text seems to correspond to MDL files in the r2d directory.

Seg54 (SW s W8) (SW s W8) 
Seg55 (SW s W8) (SW s W8) 
Seg56 (SW s W8) (SW s W8) 
Seg57 (SW s W8) (SW s W8) 
Seg58 (SW s W8) (SW s W8) 
Seg59 (SW s W8) 
Seg5A (SW s W32) (SW s W8) 
Seg5B (SW s W32) 
Seg5C (SW s W8) 
Seg5D (SW s W32) 
Seg5E (SW s W32) 
Seg5F (SW s W32) 
Seg60 (SW s W32) 
Seg61 (SW s W8) (SW s W8) 
Seg62 (SW s W8) 
Seg63 
Seg64 
Seg65Trophy 
Seg66 
Seg67 
Seg68 
Seg69 
Seg6A (SW s W8) 
Seg6B (SW s W8) 
Seg6CWipe (SW s W8) (SW s W32) (SW s W32) (SW s W32) 
Seg6DWipe (SW s W8) (SW s W32) (SW s W32) (SW s W32) 
Seg6E 
Seg6F 
Seg70 (SW s W8) (SW s W8) 
Seg71 (SW s W8) (SW s W8) 
Seg72 
Seg73Kyoro (SW s W8) (SW s W32) 
Seg74 
Seg75 (SW s W8) 
Seg76 
Seg77SCP (SW s W8) 

Instances

Instances details
Functor (Seg 'Weak) Source # 
Instance details

Defined in GTVM.SCP

Methods

fmap :: (a -> b) -> Seg 'Weak a -> Seg 'Weak b #

(<$) :: a -> Seg 'Weak b -> Seg 'Weak a #

Foldable (Seg 'Weak) Source # 
Instance details

Defined in GTVM.SCP

Methods

fold :: Monoid m => Seg 'Weak m -> m #

foldMap :: Monoid m => (a -> m) -> Seg 'Weak a -> m #

foldMap' :: Monoid m => (a -> m) -> Seg 'Weak a -> m #

foldr :: (a -> b -> b) -> b -> Seg 'Weak a -> b #

foldr' :: (a -> b -> b) -> b -> Seg 'Weak a -> b #

foldl :: (b -> a -> b) -> b -> Seg 'Weak a -> b #

foldl' :: (b -> a -> b) -> b -> Seg 'Weak a -> b #

foldr1 :: (a -> a -> a) -> Seg 'Weak a -> a #

foldl1 :: (a -> a -> a) -> Seg 'Weak a -> a #

toList :: Seg 'Weak a -> [a] #

null :: Seg 'Weak a -> Bool #

length :: Seg 'Weak a -> Int #

elem :: Eq a => a -> Seg 'Weak a -> Bool #

maximum :: Ord a => Seg 'Weak a -> a #

minimum :: Ord a => Seg 'Weak a -> a #

sum :: Num a => Seg 'Weak a -> a #

product :: Num a => Seg 'Weak a -> a #

Traversable (Seg 'Weak) Source # 
Instance details

Defined in GTVM.SCP

Methods

traverse :: Applicative f => (a -> f b) -> Seg 'Weak a -> f (Seg 'Weak b) #

sequenceA :: Applicative f => Seg 'Weak (f a) -> f (Seg 'Weak a) #

mapM :: Monad m => (a -> m b) -> Seg 'Weak a -> m (Seg 'Weak b) #

sequence :: Monad m => Seg 'Weak (m a) -> m (Seg 'Weak a) #

FromJSON a => FromJSON (Seg 'Weak a) Source # 
Instance details

Defined in GTVM.SCP

ToJSON a => ToJSON (Seg 'Weak a) Source # 
Instance details

Defined in GTVM.SCP

BLen a => BLen (Seg 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Methods

blen :: Seg 'Strong a -> Int #

Get a => Get (Seg 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Methods

get :: Getter (Seg 'Strong a) #

Put a => Put (Seg 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Methods

put :: Seg 'Strong a -> Putter #

Generic (Seg s a) Source # 
Instance details

Defined in GTVM.SCP

Associated Types

type Rep (Seg s a) 
Instance details

Defined in GTVM.SCP

type Rep (Seg s a) = D1 ('MetaData "Seg" "GTVM.SCP" "gtvm-hs-1.0.0-inplace" 'False) ((((((C1 ('MetaCons "Seg00" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Seg01BG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg02SFX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: ((C1 ('MetaCons "Seg03" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg04" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg05" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seg05Text s a))) :+: C1 ('MetaCons "Seg07SCP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))) :+: ((C1 ('MetaCons "Seg08" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Seg09Choice" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AW32Pairs s a))) :+: C1 ('MetaCons "Seg0A" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (W322Block s))))) :+: ((C1 ('MetaCons "Seg0B" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg0CFlag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg0D" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg0E" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))))) :+: (((C1 ('MetaCons "Seg0F" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Seg10" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg11EventCG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) :+: ((C1 ('MetaCons "Seg12" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg13" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))))) :+: (C1 ('MetaCons "Seg14" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg15" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Seg16Wadai" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg17" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg18" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg19" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: ((C1 ('MetaCons "Seg1D" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg1E" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg1FDelay" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg20" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))))))) :+: ((((C1 ('MetaCons "Seg21" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Seg22" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AW32Pairs s a))) :+: C1 ('MetaCons "Seg23SFX" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Seg24" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Seg25" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Seg26" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg27" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))))) :+: ((C1 ('MetaCons "Seg28" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg29" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg2A" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: ((C1 ('MetaCons "Seg2B" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (W322Block s))))) :+: C1 ('MetaCons "Seg2CMap" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Seg2D" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg2E" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)))))))) :+: (((C1 ('MetaCons "Seg2F" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: (C1 ('MetaCons "Seg30" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg31" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Seg32" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg33" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg34" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :+: C1 ('MetaCons "Seg35" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))) :+: (((C1 ('MetaCons "Seg36" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :+: C1 ('MetaCons "Seg37" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)))) :+: (C1 ('MetaCons "Seg38" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :+: C1 ('MetaCons "Seg39" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Seg3A" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg3B" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg3C" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg3D" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "Seg3E" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: (C1 ('MetaCons "Seg3F" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)))) :+: C1 ('MetaCons "Seg40" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: ((C1 ('MetaCons "Seg41" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)))) :+: C1 ('MetaCons "Seg42" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg43SFX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Seg44SFX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))) :+: ((C1 ('MetaCons "Seg45SFX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: (C1 ('MetaCons "Seg46" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg47" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: ((C1 ('MetaCons "Seg48" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg49" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Seg4A" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg4B" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Seg4C" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: (C1 ('MetaCons "Seg4D" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg4E" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Seg4F" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg50" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: (C1 ('MetaCons "Seg51" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg52" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))) :+: (((C1 ('MetaCons "Seg53" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg54" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg55" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg56" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: ((C1 ('MetaCons "Seg57" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg58" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg59" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg5A" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))))))) :+: ((((C1 ('MetaCons "Seg5B" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :+: (C1 ('MetaCons "Seg5C" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg5D" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))))) :+: ((C1 ('MetaCons "Seg5E" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :+: C1 ('MetaCons "Seg5F" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)))) :+: (C1 ('MetaCons "Seg60" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :+: C1 ('MetaCons "Seg61" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))))) :+: ((C1 ('MetaCons "Seg62" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: (C1 ('MetaCons "Seg63" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg64" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Seg65Trophy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg66" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Seg67" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg68" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Seg69" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Seg6A" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg6B" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: ((C1 ('MetaCons "Seg6CWipe" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)))) :+: C1 ('MetaCons "Seg6DWipe" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))))) :+: (C1 ('MetaCons "Seg6E" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg6F" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Seg70" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg71" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg72" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg73Kyoro" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))))) :+: ((C1 ('MetaCons "Seg74" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg75" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg76" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg77SCP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))))))))

Methods

from :: Seg s a -> Rep (Seg s a) x #

to :: Rep (Seg s a) x -> Seg s a #

Show a => Show (Seg 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Methods

showsPrec :: Int -> Seg 'Strong a -> ShowS #

show :: Seg 'Strong a -> String #

showList :: [Seg 'Strong a] -> ShowS #

Show a => Show (Seg 'Weak a) Source # 
Instance details

Defined in GTVM.SCP

Methods

showsPrec :: Int -> Seg 'Weak a -> ShowS #

show :: Seg 'Weak a -> String #

showList :: [Seg 'Weak a] -> ShowS #

Eq a => Eq (Seg 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Methods

(==) :: Seg 'Strong a -> Seg 'Strong a -> Bool #

(/=) :: Seg 'Strong a -> Seg 'Strong a -> Bool #

Eq a => Eq (Seg 'Weak a) Source # 
Instance details

Defined in GTVM.SCP

Methods

(==) :: Seg 'Weak a -> Seg 'Weak a -> Bool #

(/=) :: Seg 'Weak a -> Seg 'Weak a -> Bool #

Strengthen (Seg 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Weaken (Seg 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

Associated Types

type Weak (Seg 'Strong a) 
Instance details

Defined in GTVM.SCP

type Weak (Seg 'Strong a) = Seg 'Weak a

Methods

weaken :: Seg 'Strong a -> Weak (Seg 'Strong a) #

CstrParser Seg Source #

Second part of the Seg constructor parser instance.

Instance details

Defined in GTVM.SCP

Associated Types

type ParseCstr Seg cstr 
Instance details

Defined in GTVM.SCP

type ParseCstr Seg cstr = Run'_ ParseSeg cstr
type ReifyCstrParseResult Seg (n :: CstrParseResult Seg :: Type) 
Instance details

Defined in GTVM.SCP

CstrParser' Seg Source #

First part of the Seg constructor parser instance.

Instance details

Defined in GTVM.SCP

Associated Types

type CstrParseResult Seg 
Instance details

Defined in GTVM.SCP

type Rep (Seg s a) Source # 
Instance details

Defined in GTVM.SCP

type Rep (Seg s a) = D1 ('MetaData "Seg" "GTVM.SCP" "gtvm-hs-1.0.0-inplace" 'False) ((((((C1 ('MetaCons "Seg00" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Seg01BG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg02SFX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: ((C1 ('MetaCons "Seg03" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg04" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg05" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seg05Text s a))) :+: C1 ('MetaCons "Seg07SCP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))) :+: ((C1 ('MetaCons "Seg08" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Seg09Choice" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AW32Pairs s a))) :+: C1 ('MetaCons "Seg0A" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (W322Block s))))) :+: ((C1 ('MetaCons "Seg0B" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg0CFlag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg0D" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg0E" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))))) :+: (((C1 ('MetaCons "Seg0F" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Seg10" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg11EventCG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) :+: ((C1 ('MetaCons "Seg12" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg13" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))))) :+: (C1 ('MetaCons "Seg14" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg15" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Seg16Wadai" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg17" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg18" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg19" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: ((C1 ('MetaCons "Seg1D" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg1E" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg1FDelay" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg20" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))))))) :+: ((((C1 ('MetaCons "Seg21" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Seg22" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AW32Pairs s a))) :+: C1 ('MetaCons "Seg23SFX" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Seg24" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Seg25" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Seg26" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg27" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))))) :+: ((C1 ('MetaCons "Seg28" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg29" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg2A" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: ((C1 ('MetaCons "Seg2B" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (W322Block s))))) :+: C1 ('MetaCons "Seg2CMap" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Seg2D" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg2E" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)))))))) :+: (((C1 ('MetaCons "Seg2F" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: (C1 ('MetaCons "Seg30" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg31" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Seg32" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg33" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg34" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :+: C1 ('MetaCons "Seg35" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))) :+: (((C1 ('MetaCons "Seg36" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :+: C1 ('MetaCons "Seg37" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)))) :+: (C1 ('MetaCons "Seg38" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :+: C1 ('MetaCons "Seg39" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Seg3A" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg3B" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg3C" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg3D" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "Seg3E" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: (C1 ('MetaCons "Seg3F" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)))) :+: C1 ('MetaCons "Seg40" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: ((C1 ('MetaCons "Seg41" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)))) :+: C1 ('MetaCons "Seg42" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg43SFX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Seg44SFX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))) :+: ((C1 ('MetaCons "Seg45SFX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: (C1 ('MetaCons "Seg46" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg47" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: ((C1 ('MetaCons "Seg48" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg49" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Seg4A" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg4B" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Seg4C" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: (C1 ('MetaCons "Seg4D" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg4E" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Seg4F" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg50" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: (C1 ('MetaCons "Seg51" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg52" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))) :+: (((C1 ('MetaCons "Seg53" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: C1 ('MetaCons "Seg54" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg55" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg56" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: ((C1 ('MetaCons "Seg57" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg58" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg59" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg5A" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))))))) :+: ((((C1 ('MetaCons "Seg5B" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :+: (C1 ('MetaCons "Seg5C" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg5D" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))))) :+: ((C1 ('MetaCons "Seg5E" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :+: C1 ('MetaCons "Seg5F" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)))) :+: (C1 ('MetaCons "Seg60" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :+: C1 ('MetaCons "Seg61" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))))) :+: ((C1 ('MetaCons "Seg62" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: (C1 ('MetaCons "Seg63" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg64" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Seg65Trophy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg66" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Seg67" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg68" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Seg69" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Seg6A" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg6B" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))) :+: ((C1 ('MetaCons "Seg6CWipe" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)))) :+: C1 ('MetaCons "Seg6DWipe" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))))) :+: (C1 ('MetaCons "Seg6E" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg6F" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Seg70" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))) :+: C1 ('MetaCons "Seg71" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg72" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg73Kyoro" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W32))))) :+: ((C1 ('MetaCons "Seg74" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg75" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8)))) :+: (C1 ('MetaCons "Seg76" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Seg77SCP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SW s W8))))))))))
type Weak (Seg 'Strong a) Source # 
Instance details

Defined in GTVM.SCP

type Weak (Seg 'Strong a) = Seg 'Weak a
type CstrParseResult Seg Source # 
Instance details

Defined in GTVM.SCP

type ParseCstr Seg cstr Source # 
Instance details

Defined in GTVM.SCP

type ParseCstr Seg cstr = Run'_ ParseSeg cstr
type ReifyCstrParseResult Seg (n :: CstrParseResult Seg :: Type) Source # 
Instance details

Defined in GTVM.SCP

type ParseSeg = Literal "Seg" :*>: Isolate 2 NatHex Source #

Parse SegXX, where XX is a hexadecimal number.

This is a Symparsec type-level string parser. We use it to parse the Seg constructors on the type level, when deriving generic binrep instances. See the symparsec package for more details.

jcSeg :: Options Source #

Seg JSON config.

If aeson were better, we would do this in types like binrep, but alas.

type SCP (s :: Strength) a = [Seg s a] Source #

The SCP format.

The SCP format is very simple: it is a concatenated list of segments. There is no length indicator; EOF is used to indicate no more segments. This is precisely how the binrep List instance works, so we leverage it.

scpFmap :: (a -> b) -> SCP 'Weak a -> SCP 'Weak b Source #

scpTraverse :: Applicative f => (a -> f b) -> SCP 'Weak a -> f (SCP 'Weak b) Source #