ldtk-types-1.2.3: Datatypes and Aeson instances for parsing LDtk
Safe HaskellNone
LanguageHaskell2010

LDtk

Synopsis

Documentation

data Field Source #

Instances

Instances details
Eq Field Source # 
Instance details

Defined in LDtk.Types

Methods

(==) :: Field -> Field -> Bool #

(/=) :: Field -> Field -> Bool #

Ord Field Source # 
Instance details

Defined in LDtk.Types

Methods

compare :: Field -> Field -> Ordering #

(<) :: Field -> Field -> Bool #

(<=) :: Field -> Field -> Bool #

(>) :: Field -> Field -> Bool #

(>=) :: Field -> Field -> Bool #

max :: Field -> Field -> Field #

min :: Field -> Field -> Field #

Read Field Source # 
Instance details

Defined in LDtk.Types

Show Field Source # 
Instance details

Defined in LDtk.Types

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

Generic Field Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep Field :: Type -> Type #

Methods

from :: Field -> Rep Field x #

to :: Rep Field x -> Field #

FromJSON Field Source # 
Instance details

Defined in LDtk.Types

type Rep Field Source # 
Instance details

Defined in LDtk.Types

data Entity Source #

Instances

Instances details
Eq Entity Source # 
Instance details

Defined in LDtk.Types

Methods

(==) :: Entity -> Entity -> Bool #

(/=) :: Entity -> Entity -> Bool #

Ord Entity Source # 
Instance details

Defined in LDtk.Types

Read Entity Source # 
Instance details

Defined in LDtk.Types

Show Entity Source # 
Instance details

Defined in LDtk.Types

Generic Entity Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep Entity :: Type -> Type #

Methods

from :: Entity -> Rep Entity x #

to :: Rep Entity x -> Entity #

FromJSON Entity Source # 
Instance details

Defined in LDtk.Types

type Rep Entity Source # 
Instance details

Defined in LDtk.Types

data Tile Source #

Constructors

Tile 

Fields

Instances

Instances details
Eq Tile Source # 
Instance details

Defined in LDtk.Types

Methods

(==) :: Tile -> Tile -> Bool #

(/=) :: Tile -> Tile -> Bool #

Ord Tile Source # 
Instance details

Defined in LDtk.Types

Methods

compare :: Tile -> Tile -> Ordering #

(<) :: Tile -> Tile -> Bool #

(<=) :: Tile -> Tile -> Bool #

(>) :: Tile -> Tile -> Bool #

(>=) :: Tile -> Tile -> Bool #

max :: Tile -> Tile -> Tile #

min :: Tile -> Tile -> Tile #

Read Tile Source # 
Instance details

Defined in LDtk.Types

Show Tile Source # 
Instance details

Defined in LDtk.Types

Methods

showsPrec :: Int -> Tile -> ShowS #

show :: Tile -> String #

showList :: [Tile] -> ShowS #

Generic Tile Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep Tile :: Type -> Type #

Methods

from :: Tile -> Rep Tile x #

to :: Rep Tile x -> Tile #

FromJSON Tile Source # 
Instance details

Defined in LDtk.Types

type Rep Tile Source # 
Instance details

Defined in LDtk.Types

data TilesetRect Source #

Constructors

TilesetRect 

Fields

Instances

Instances details
Eq TilesetRect Source # 
Instance details

Defined in LDtk.Types

Ord TilesetRect Source # 
Instance details

Defined in LDtk.Types

Read TilesetRect Source # 
Instance details

Defined in LDtk.Types

Show TilesetRect Source # 
Instance details

Defined in LDtk.Types

Generic TilesetRect Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep TilesetRect :: Type -> Type #

FromJSON TilesetRect Source # 
Instance details

Defined in LDtk.Types

type Rep TilesetRect Source # 
Instance details

Defined in LDtk.Types

data FieldValue Source #

Instances

Instances details
Eq FieldValue Source # 
Instance details

Defined in LDtk.Types

Ord FieldValue Source # 
Instance details

Defined in LDtk.Types

Read FieldValue Source # 
Instance details

Defined in LDtk.Types

Show FieldValue Source # 
Instance details

Defined in LDtk.Types

Generic FieldValue Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep FieldValue :: Type -> Type #

type Rep FieldValue Source # 
Instance details

Defined in LDtk.Types

type Rep FieldValue = D1 ('MetaData "FieldValue" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (((C1 ('MetaCons "IntegerValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: C1 ('MetaCons "FloatValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))) :+: (C1 ('MetaCons "BooleanValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: (C1 ('MetaCons "StringValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "FilePathValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath))))) :+: ((C1 ('MetaCons "ColorValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color)) :+: (C1 ('MetaCons "EnumValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "PointValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GridPoint)))) :+: (C1 ('MetaCons "TileValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TilesetRect)) :+: (C1 ('MetaCons "EntityRefValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EntityReferenceInfos)) :+: C1 ('MetaCons "ArrayValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldValue]))))))

data EntityReferenceInfos Source #

Instances

Instances details
Eq EntityReferenceInfos Source # 
Instance details

Defined in LDtk.Types

Ord EntityReferenceInfos Source # 
Instance details

Defined in LDtk.Types

Read EntityReferenceInfos Source # 
Instance details

Defined in LDtk.Types

Show EntityReferenceInfos Source # 
Instance details

Defined in LDtk.Types

Generic EntityReferenceInfos Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep EntityReferenceInfos :: Type -> Type #

FromJSON EntityReferenceInfos Source # 
Instance details

Defined in LDtk.Types

type Rep EntityReferenceInfos Source # 
Instance details

Defined in LDtk.Types

type Rep EntityReferenceInfos = D1 ('MetaData "EntityReferenceInfos" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "EntityReferenceInfos" 'PrefixI 'True) ((S1 ('MetaSel ('Just "entityIid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "layerIid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "levelIid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "worldIid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

data Flip Source #

Constructors

NoFlip 
FlipX 
FlipY 
FlipXY 

Instances

Instances details
Bounded Flip Source # 
Instance details

Defined in LDtk.Types

Enum Flip Source # 
Instance details

Defined in LDtk.Types

Methods

succ :: Flip -> Flip #

pred :: Flip -> Flip #

toEnum :: Int -> Flip #

fromEnum :: Flip -> Int #

enumFrom :: Flip -> [Flip] #

enumFromThen :: Flip -> Flip -> [Flip] #

enumFromTo :: Flip -> Flip -> [Flip] #

enumFromThenTo :: Flip -> Flip -> Flip -> [Flip] #

Eq Flip Source # 
Instance details

Defined in LDtk.Types

Methods

(==) :: Flip -> Flip -> Bool #

(/=) :: Flip -> Flip -> Bool #

Ord Flip Source # 
Instance details

Defined in LDtk.Types

Methods

compare :: Flip -> Flip -> Ordering #

(<) :: Flip -> Flip -> Bool #

(<=) :: Flip -> Flip -> Bool #

(>) :: Flip -> Flip -> Bool #

(>=) :: Flip -> Flip -> Bool #

max :: Flip -> Flip -> Flip #

min :: Flip -> Flip -> Flip #

Read Flip Source # 
Instance details

Defined in LDtk.Types

Show Flip Source # 
Instance details

Defined in LDtk.Types

Methods

showsPrec :: Int -> Flip -> ShowS #

show :: Flip -> String #

showList :: [Flip] -> ShowS #

Generic Flip Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep Flip :: Type -> Type #

Methods

from :: Flip -> Rep Flip x #

to :: Rep Flip x -> Flip #

FromJSON Flip Source # 
Instance details

Defined in LDtk.Types

type Rep Flip Source # 
Instance details

Defined in LDtk.Types

type Rep Flip = D1 ('MetaData "Flip" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) ((C1 ('MetaCons "NoFlip" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FlipX" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FlipY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FlipXY" 'PrefixI 'False) (U1 :: Type -> Type)))

data Pair a Source #

Constructors

Pair 

Fields

Instances

Instances details
Eq a => Eq (Pair a) Source # 
Instance details

Defined in LDtk.Types

Methods

(==) :: Pair a -> Pair a -> Bool #

(/=) :: Pair a -> Pair a -> Bool #

Ord a => Ord (Pair a) Source # 
Instance details

Defined in LDtk.Types

Methods

compare :: Pair a -> Pair a -> Ordering #

(<) :: Pair a -> Pair a -> Bool #

(<=) :: Pair a -> Pair a -> Bool #

(>) :: Pair a -> Pair a -> Bool #

(>=) :: Pair a -> Pair a -> Bool #

max :: Pair a -> Pair a -> Pair a #

min :: Pair a -> Pair a -> Pair a #

Read a => Read (Pair a) Source # 
Instance details

Defined in LDtk.Types

Show a => Show (Pair a) Source # 
Instance details

Defined in LDtk.Types

Methods

showsPrec :: Int -> Pair a -> ShowS #

show :: Pair a -> String #

showList :: [Pair a] -> ShowS #

Generic (Pair a) Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep (Pair a) :: Type -> Type #

Methods

from :: Pair a -> Rep (Pair a) x #

to :: Rep (Pair a) x -> Pair a #

FromJSON a => FromJSON (Pair a) Source # 
Instance details

Defined in LDtk.Types

type Rep (Pair a) Source # 
Instance details

Defined in LDtk.Types

type Rep (Pair a) = D1 ('MetaData "Pair" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "Pair" 'PrefixI 'True) (S1 ('MetaSel ('Just "p_x") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "p_y") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

data GridPoint Source #

Constructors

GridPoint 

Fields

Instances

Instances details
Eq GridPoint Source # 
Instance details

Defined in LDtk.Types

Ord GridPoint Source # 
Instance details

Defined in LDtk.Types

Read GridPoint Source # 
Instance details

Defined in LDtk.Types

Show GridPoint Source # 
Instance details

Defined in LDtk.Types

Generic GridPoint Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep GridPoint :: Type -> Type #

FromJSON GridPoint Source # 
Instance details

Defined in LDtk.Types

type Rep GridPoint Source # 
Instance details

Defined in LDtk.Types

type Rep GridPoint = D1 ('MetaData "GridPoint" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "GridPoint" 'PrefixI 'True) (S1 ('MetaSel ('Just "cx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "cy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data Layer Source #

Instances

Instances details
Eq Layer Source # 
Instance details

Defined in LDtk.Types

Methods

(==) :: Layer -> Layer -> Bool #

(/=) :: Layer -> Layer -> Bool #

Ord Layer Source # 
Instance details

Defined in LDtk.Types

Methods

compare :: Layer -> Layer -> Ordering #

(<) :: Layer -> Layer -> Bool #

(<=) :: Layer -> Layer -> Bool #

(>) :: Layer -> Layer -> Bool #

(>=) :: Layer -> Layer -> Bool #

max :: Layer -> Layer -> Layer #

min :: Layer -> Layer -> Layer #

Read Layer Source # 
Instance details

Defined in LDtk.Types

Show Layer Source # 
Instance details

Defined in LDtk.Types

Methods

showsPrec :: Int -> Layer -> ShowS #

show :: Layer -> String #

showList :: [Layer] -> ShowS #

Generic Layer Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep Layer :: Type -> Type #

Methods

from :: Layer -> Rep Layer x #

to :: Rep Layer x -> Layer #

FromJSON Layer Source # 
Instance details

Defined in LDtk.Types

type Rep Layer Source # 
Instance details

Defined in LDtk.Types

type Rep Layer = D1 ('MetaData "Layer" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "Layer" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "__cHei") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "__cWid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "__gridSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "__identifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "__opacity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)))) :*: ((S1 ('MetaSel ('Just "__pxTotalOffsetX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "__pxTotalOffsetY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "__tilesetDefUid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "__tilesetRelPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "__type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LayerType))))) :*: (((S1 ('MetaSel ('Just "autoLayerTiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tile]) :*: S1 ('MetaSel ('Just "entityInstances") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Entity])) :*: (S1 ('MetaSel ('Just "gridTiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tile]) :*: (S1 ('MetaSel ('Just "iid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "intGridCsv") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int])))) :*: ((S1 ('MetaSel ('Just "layerDefUid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "tilesetRelPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "levelId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "overrideTilesetUid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "visible") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))))

data Level Source #

Instances

Instances details
Eq Level Source # 
Instance details

Defined in LDtk.Types

Methods

(==) :: Level -> Level -> Bool #

(/=) :: Level -> Level -> Bool #

Ord Level Source # 
Instance details

Defined in LDtk.Types

Methods

compare :: Level -> Level -> Ordering #

(<) :: Level -> Level -> Bool #

(<=) :: Level -> Level -> Bool #

(>) :: Level -> Level -> Bool #

(>=) :: Level -> Level -> Bool #

max :: Level -> Level -> Level #

min :: Level -> Level -> Level #

Read Level Source # 
Instance details

Defined in LDtk.Types

Show Level Source # 
Instance details

Defined in LDtk.Types

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

Generic Level Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep Level :: Type -> Type #

Methods

from :: Level -> Rep Level x #

to :: Rep Level x -> Level #

FromJSON Level Source # 
Instance details

Defined in LDtk.Types

type Rep Level Source # 
Instance details

Defined in LDtk.Types

type Rep Level = D1 ('MetaData "Level" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "Level" 'PrefixI 'True) (((S1 ('MetaSel ('Just "__bgColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color) :*: (S1 ('MetaSel ('Just "__bgPos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BgPos)) :*: S1 ('MetaSel ('Just "__neighbours") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Neighbour]))) :*: ((S1 ('MetaSel ('Just "bgRelPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "externalRelPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "fieldInstances") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Field]) :*: S1 ('MetaSel ('Just "identifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) :*: (((S1 ('MetaSel ('Just "iid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "layerInstances") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Layer])) :*: (S1 ('MetaSel ('Just "pxHei") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "pxWid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :*: ((S1 ('MetaSel ('Just "uid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "worldDepth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "worldX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "worldY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))))

data Neighbour Source #

Constructors

Neighbour 

Fields

Instances

Instances details
Eq Neighbour Source # 
Instance details

Defined in LDtk.Types

Ord Neighbour Source # 
Instance details

Defined in LDtk.Types

Read Neighbour Source # 
Instance details

Defined in LDtk.Types

Show Neighbour Source # 
Instance details

Defined in LDtk.Types

Generic Neighbour Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep Neighbour :: Type -> Type #

FromJSON Neighbour Source # 
Instance details

Defined in LDtk.Types

type Rep Neighbour Source # 
Instance details

Defined in LDtk.Types

type Rep Neighbour = D1 ('MetaData "Neighbour" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "Neighbour" 'PrefixI 'True) (S1 ('MetaSel ('Just "dir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Direction) :*: S1 ('MetaSel ('Just "levelIid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Direction Source #

Constructors

North 
South 
East 
West 

Instances

Instances details
Eq Direction Source # 
Instance details

Defined in LDtk.Types

Ord Direction Source # 
Instance details

Defined in LDtk.Types

Read Direction Source # 
Instance details

Defined in LDtk.Types

Show Direction Source # 
Instance details

Defined in LDtk.Types

Generic Direction Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep Direction :: Type -> Type #

FromJSON Direction Source # 
Instance details

Defined in LDtk.Types

type Rep Direction Source # 
Instance details

Defined in LDtk.Types

type Rep Direction = D1 ('MetaData "Direction" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) ((C1 ('MetaCons "North" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "South" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "East" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "West" 'PrefixI 'False) (U1 :: Type -> Type)))

data BgPos Source #

Constructors

BgPos 

Instances

Instances details
Eq BgPos Source # 
Instance details

Defined in LDtk.Types

Methods

(==) :: BgPos -> BgPos -> Bool #

(/=) :: BgPos -> BgPos -> Bool #

Ord BgPos Source # 
Instance details

Defined in LDtk.Types

Methods

compare :: BgPos -> BgPos -> Ordering #

(<) :: BgPos -> BgPos -> Bool #

(<=) :: BgPos -> BgPos -> Bool #

(>) :: BgPos -> BgPos -> Bool #

(>=) :: BgPos -> BgPos -> Bool #

max :: BgPos -> BgPos -> BgPos #

min :: BgPos -> BgPos -> BgPos #

Read BgPos Source # 
Instance details

Defined in LDtk.Types

Show BgPos Source # 
Instance details

Defined in LDtk.Types

Methods

showsPrec :: Int -> BgPos -> ShowS #

show :: BgPos -> String #

showList :: [BgPos] -> ShowS #

Generic BgPos Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep BgPos :: Type -> Type #

Methods

from :: BgPos -> Rep BgPos x #

to :: Rep BgPos x -> BgPos #

FromJSON BgPos Source # 
Instance details

Defined in LDtk.Types

type Rep BgPos Source # 
Instance details

Defined in LDtk.Types

type Rep BgPos = D1 ('MetaData "BgPos" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "BgPos" 'PrefixI 'True) (S1 ('MetaSel ('Just "cropRect") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Rect Float)) :*: (S1 ('MetaSel ('Just "scale") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pair Float)) :*: S1 ('MetaSel ('Just "topLeftPx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pair Int)))))

data Rect a Source #

Constructors

Rect 

Fields

Instances

Instances details
Eq a => Eq (Rect a) Source # 
Instance details

Defined in LDtk.Types

Methods

(==) :: Rect a -> Rect a -> Bool #

(/=) :: Rect a -> Rect a -> Bool #

Ord a => Ord (Rect a) Source # 
Instance details

Defined in LDtk.Types

Methods

compare :: Rect a -> Rect a -> Ordering #

(<) :: Rect a -> Rect a -> Bool #

(<=) :: Rect a -> Rect a -> Bool #

(>) :: Rect a -> Rect a -> Bool #

(>=) :: Rect a -> Rect a -> Bool #

max :: Rect a -> Rect a -> Rect a #

min :: Rect a -> Rect a -> Rect a #

Read a => Read (Rect a) Source # 
Instance details

Defined in LDtk.Types

Show a => Show (Rect a) Source # 
Instance details

Defined in LDtk.Types

Methods

showsPrec :: Int -> Rect a -> ShowS #

show :: Rect a -> String #

showList :: [Rect a] -> ShowS #

Generic (Rect a) Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep (Rect a) :: Type -> Type #

Methods

from :: Rect a -> Rep (Rect a) x #

to :: Rep (Rect a) x -> Rect a #

FromJSON a => FromJSON (Rect a) Source # 
Instance details

Defined in LDtk.Types

type Rep (Rect a) Source # 
Instance details

Defined in LDtk.Types

type Rep (Rect a) = D1 ('MetaData "Rect" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "Rect" 'PrefixI 'True) ((S1 ('MetaSel ('Just "r_x") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "r_y") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :*: (S1 ('MetaSel ('Just "r_width") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "r_height") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))

data World Source #

Instances

Instances details
Eq World Source # 
Instance details

Defined in LDtk.Types

Methods

(==) :: World -> World -> Bool #

(/=) :: World -> World -> Bool #

Ord World Source # 
Instance details

Defined in LDtk.Types

Methods

compare :: World -> World -> Ordering #

(<) :: World -> World -> Bool #

(<=) :: World -> World -> Bool #

(>) :: World -> World -> Bool #

(>=) :: World -> World -> Bool #

max :: World -> World -> World #

min :: World -> World -> World #

Read World Source # 
Instance details

Defined in LDtk.Types

Show World Source # 
Instance details

Defined in LDtk.Types

Methods

showsPrec :: Int -> World -> ShowS #

show :: World -> String #

showList :: [World] -> ShowS #

Generic World Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep World :: Type -> Type #

Methods

from :: World -> Rep World x #

to :: Rep World x -> World #

FromJSON World Source # 
Instance details

Defined in LDtk.Types

type Rep World Source # 
Instance details

Defined in LDtk.Types

data LayerType Source #

Constructors

IntGrid 
Entities 
Tiles 
AutoLayer 

Instances

Instances details
Bounded LayerType Source # 
Instance details

Defined in LDtk.Types

Enum LayerType Source # 
Instance details

Defined in LDtk.Types

Eq LayerType Source # 
Instance details

Defined in LDtk.Types

Ord LayerType Source # 
Instance details

Defined in LDtk.Types

Read LayerType Source # 
Instance details

Defined in LDtk.Types

Show LayerType Source # 
Instance details

Defined in LDtk.Types

Generic LayerType Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep LayerType :: Type -> Type #

FromJSON LayerType Source # 
Instance details

Defined in LDtk.Types

type Rep LayerType Source # 
Instance details

Defined in LDtk.Types

type Rep LayerType = D1 ('MetaData "LayerType" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) ((C1 ('MetaCons "IntGrid" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Entities" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Tiles" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AutoLayer" 'PrefixI 'False) (U1 :: Type -> Type)))

data WorldLayout Source #

Instances

Instances details
Bounded WorldLayout Source # 
Instance details

Defined in LDtk.Types

Enum WorldLayout Source # 
Instance details

Defined in LDtk.Types

Eq WorldLayout Source # 
Instance details

Defined in LDtk.Types

Ord WorldLayout Source # 
Instance details

Defined in LDtk.Types

Read WorldLayout Source # 
Instance details

Defined in LDtk.Types

Show WorldLayout Source # 
Instance details

Defined in LDtk.Types

Generic WorldLayout Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep WorldLayout :: Type -> Type #

FromJSON WorldLayout Source # 
Instance details

Defined in LDtk.Types

type Rep WorldLayout Source # 
Instance details

Defined in LDtk.Types

type Rep WorldLayout = D1 ('MetaData "WorldLayout" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) ((C1 ('MetaCons "Free" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GridVania" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LinearHorizontal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LinearVertical" 'PrefixI 'False) (U1 :: Type -> Type)))

data TileRenderMode Source #

Instances

Instances details
Bounded TileRenderMode Source # 
Instance details

Defined in LDtk.Types

Enum TileRenderMode Source # 
Instance details

Defined in LDtk.Types

Eq TileRenderMode Source # 
Instance details

Defined in LDtk.Types

Ord TileRenderMode Source # 
Instance details

Defined in LDtk.Types

Read TileRenderMode Source # 
Instance details

Defined in LDtk.Types

Show TileRenderMode Source # 
Instance details

Defined in LDtk.Types

Generic TileRenderMode Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep TileRenderMode :: Type -> Type #

FromJSON TileRenderMode Source # 
Instance details

Defined in LDtk.Types

type Rep TileRenderMode Source # 
Instance details

Defined in LDtk.Types

type Rep TileRenderMode = D1 ('MetaData "TileRenderMode" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) ((C1 ('MetaCons "Cover" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FitInside" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Repeat" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Stretch" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FullSizeCropped" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FillSizeUncropped" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NineSlice" 'PrefixI 'False) (U1 :: Type -> Type))))

data LDtkRoot Source #

Instances

Instances details
Eq LDtkRoot Source # 
Instance details

Defined in LDtk.Types

Ord LDtkRoot Source # 
Instance details

Defined in LDtk.Types

Read LDtkRoot Source # 
Instance details

Defined in LDtk.Types

Show LDtkRoot Source # 
Instance details

Defined in LDtk.Types

Generic LDtkRoot Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep LDtkRoot :: Type -> Type #

Methods

from :: LDtkRoot -> Rep LDtkRoot x #

to :: Rep LDtkRoot x -> LDtkRoot #

FromJSON LDtkRoot Source # 
Instance details

Defined in LDtk.Types

type Rep LDtkRoot Source # 
Instance details

Defined in LDtk.Types

data LayerDef Source #

Instances

Instances details
Eq LayerDef Source # 
Instance details

Defined in LDtk.Types

Ord LayerDef Source # 
Instance details

Defined in LDtk.Types

Read LayerDef Source # 
Instance details

Defined in LDtk.Types

Show LayerDef Source # 
Instance details

Defined in LDtk.Types

Generic LayerDef Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep LayerDef :: Type -> Type #

Methods

from :: LayerDef -> Rep LayerDef x #

to :: Rep LayerDef x -> LayerDef #

FromJSON LayerDef Source # 
Instance details

Defined in LDtk.Types

type Rep LayerDef Source # 
Instance details

Defined in LDtk.Types

type Rep LayerDef = D1 ('MetaData "LayerDef" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "LayerDef" 'PrefixI 'True) (((S1 ('MetaSel ('Just "__type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LayerType) :*: (S1 ('MetaSel ('Just "autoSourceLayerDefUid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "displayOpacity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))) :*: (S1 ('MetaSel ('Just "gridSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "identifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "intGridValues") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GridValue])))) :*: ((S1 ('MetaSel ('Just "parallaxFactorX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float) :*: (S1 ('MetaSel ('Just "parallaxFactorY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float) :*: S1 ('MetaSel ('Just "parallaxScaling") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "pxOffsetX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "pxOffsetY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "tilesetDefUid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "uid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))))

data GridValue Source #

Constructors

GridValue 

Fields

Instances

Instances details
Eq GridValue Source # 
Instance details

Defined in LDtk.Types

Ord GridValue Source # 
Instance details

Defined in LDtk.Types

Read GridValue Source # 
Instance details

Defined in LDtk.Types

Show GridValue Source # 
Instance details

Defined in LDtk.Types

Generic GridValue Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep GridValue :: Type -> Type #

FromJSON GridValue Source # 
Instance details

Defined in LDtk.Types

type Rep GridValue Source # 
Instance details

Defined in LDtk.Types

type Rep GridValue = D1 ('MetaData "GridValue" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "GridValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "color") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color) :*: (S1 ('MetaSel ('Just "identifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

data EnumDef Source #

Instances

Instances details
Eq EnumDef Source # 
Instance details

Defined in LDtk.Types

Methods

(==) :: EnumDef -> EnumDef -> Bool #

(/=) :: EnumDef -> EnumDef -> Bool #

Ord EnumDef Source # 
Instance details

Defined in LDtk.Types

Read EnumDef Source # 
Instance details

Defined in LDtk.Types

Show EnumDef Source # 
Instance details

Defined in LDtk.Types

Generic EnumDef Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep EnumDef :: Type -> Type #

Methods

from :: EnumDef -> Rep EnumDef x #

to :: Rep EnumDef x -> EnumDef #

FromJSON EnumDef Source # 
Instance details

Defined in LDtk.Types

type Rep EnumDef Source # 
Instance details

Defined in LDtk.Types

data EnumValueDef Source #

Constructors

EnumValueDef 

Instances

Instances details
Eq EnumValueDef Source # 
Instance details

Defined in LDtk.Types

Ord EnumValueDef Source # 
Instance details

Defined in LDtk.Types

Read EnumValueDef Source # 
Instance details

Defined in LDtk.Types

Show EnumValueDef Source # 
Instance details

Defined in LDtk.Types

Generic EnumValueDef Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep EnumValueDef :: Type -> Type #

FromJSON EnumValueDef Source # 
Instance details

Defined in LDtk.Types

type Rep EnumValueDef Source # 
Instance details

Defined in LDtk.Types

type Rep EnumValueDef = D1 ('MetaData "EnumValueDef" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "EnumValueDef" 'PrefixI 'True) ((S1 ('MetaSel ('Just "__tileSrcRect") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Rect Int))) :*: S1 ('MetaSel ('Just "color") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "enumid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "tileId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))))

data Definitions Source #

Instances

Instances details
Eq Definitions Source # 
Instance details

Defined in LDtk.Types

Ord Definitions Source # 
Instance details

Defined in LDtk.Types

Read Definitions Source # 
Instance details

Defined in LDtk.Types

Show Definitions Source # 
Instance details

Defined in LDtk.Types

Generic Definitions Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep Definitions :: Type -> Type #

FromJSON Definitions Source # 
Instance details

Defined in LDtk.Types

type Rep Definitions Source # 
Instance details

Defined in LDtk.Types

data TilesetDef Source #

Instances

Instances details
Eq TilesetDef Source # 
Instance details

Defined in LDtk.Types

Ord TilesetDef Source # 
Instance details

Defined in LDtk.Types

Read TilesetDef Source # 
Instance details

Defined in LDtk.Types

Show TilesetDef Source # 
Instance details

Defined in LDtk.Types

Generic TilesetDef Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep TilesetDef :: Type -> Type #

FromJSON TilesetDef Source # 
Instance details

Defined in LDtk.Types

type Rep TilesetDef Source # 
Instance details

Defined in LDtk.Types

type Rep TilesetDef = D1 ('MetaData "TilesetDef" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "TilesetDef" 'PrefixI 'True) (((S1 ('MetaSel ('Just "__cHei") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "__cWid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "customData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CustomData]))) :*: ((S1 ('MetaSel ('Just "embedAtlas") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EmbedAtlas)) :*: S1 ('MetaSel ('Just "enumTags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [EnumTag])) :*: (S1 ('MetaSel ('Just "identifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "padding") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))) :*: (((S1 ('MetaSel ('Just "pxHei") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "pxWid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "relPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)) :*: S1 ('MetaSel ('Just "spacing") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :*: ((S1 ('MetaSel ('Just "tags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "tagsSourceEnumUid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "tileGridSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "uid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))))

data EnumTag Source #

Constructors

EnumTag 

Fields

Instances

Instances details
Eq EnumTag Source # 
Instance details

Defined in LDtk.Types

Methods

(==) :: EnumTag -> EnumTag -> Bool #

(/=) :: EnumTag -> EnumTag -> Bool #

Ord EnumTag Source # 
Instance details

Defined in LDtk.Types

Read EnumTag Source # 
Instance details

Defined in LDtk.Types

Show EnumTag Source # 
Instance details

Defined in LDtk.Types

Generic EnumTag Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep EnumTag :: Type -> Type #

Methods

from :: EnumTag -> Rep EnumTag x #

to :: Rep EnumTag x -> EnumTag #

FromJSON EnumTag Source # 
Instance details

Defined in LDtk.Types

type Rep EnumTag Source # 
Instance details

Defined in LDtk.Types

type Rep EnumTag = D1 ('MetaData "EnumTag" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "EnumTag" 'PrefixI 'True) (S1 ('MetaSel ('Just "enumValueId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "tileIds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int])))

data CustomData Source #

Constructors

CustomData 

Fields

Instances

Instances details
Eq CustomData Source # 
Instance details

Defined in LDtk.Types

Ord CustomData Source # 
Instance details

Defined in LDtk.Types

Read CustomData Source # 
Instance details

Defined in LDtk.Types

Show CustomData Source # 
Instance details

Defined in LDtk.Types

Generic CustomData Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep CustomData :: Type -> Type #

FromJSON CustomData Source # 
Instance details

Defined in LDtk.Types

type Rep CustomData Source # 
Instance details

Defined in LDtk.Types

type Rep CustomData = D1 ('MetaData "CustomData" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "CustomData" 'PrefixI 'True) (S1 ('MetaSel ('Just "data'") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "tileId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data EmbedAtlas Source #

Constructors

LdtkIcons 

Instances

Instances details
Bounded EmbedAtlas Source # 
Instance details

Defined in LDtk.Types

Enum EmbedAtlas Source # 
Instance details

Defined in LDtk.Types

Eq EmbedAtlas Source # 
Instance details

Defined in LDtk.Types

Ord EmbedAtlas Source # 
Instance details

Defined in LDtk.Types

Read EmbedAtlas Source # 
Instance details

Defined in LDtk.Types

Show EmbedAtlas Source # 
Instance details

Defined in LDtk.Types

Generic EmbedAtlas Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep EmbedAtlas :: Type -> Type #

FromJSON EmbedAtlas Source # 
Instance details

Defined in LDtk.Types

type Rep EmbedAtlas Source # 
Instance details

Defined in LDtk.Types

type Rep EmbedAtlas = D1 ('MetaData "EmbedAtlas" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "LdtkIcons" 'PrefixI 'False) (U1 :: Type -> Type))

data EntityDef Source #

Instances

Instances details
Eq EntityDef Source # 
Instance details

Defined in LDtk.Types

Ord EntityDef Source # 
Instance details

Defined in LDtk.Types

Read EntityDef Source # 
Instance details

Defined in LDtk.Types

Show EntityDef Source # 
Instance details

Defined in LDtk.Types

Generic EntityDef Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep EntityDef :: Type -> Type #

FromJSON EntityDef Source # 
Instance details

Defined in LDtk.Types

type Rep EntityDef Source # 
Instance details

Defined in LDtk.Types

data Color Source #

Constructors

Color 

Fields

Instances

Instances details
Eq Color Source # 
Instance details

Defined in LDtk.Types

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

Ord Color Source # 
Instance details

Defined in LDtk.Types

Methods

compare :: Color -> Color -> Ordering #

(<) :: Color -> Color -> Bool #

(<=) :: Color -> Color -> Bool #

(>) :: Color -> Color -> Bool #

(>=) :: Color -> Color -> Bool #

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

Read Color Source # 
Instance details

Defined in LDtk.Types

Show Color Source # 
Instance details

Defined in LDtk.Types

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Generic Color Source # 
Instance details

Defined in LDtk.Types

Associated Types

type Rep Color :: Type -> Type #

Methods

from :: Color -> Rep Color x #

to :: Rep Color x -> Color #

FromJSON Color Source # 
Instance details

Defined in LDtk.Types

type Rep Color Source # 
Instance details

Defined in LDtk.Types

type Rep Color = D1 ('MetaData "Color" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "Color" 'PrefixI 'True) (S1 ('MetaSel ('Just "c_r") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: (S1 ('MetaSel ('Just "c_g") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: S1 ('MetaSel ('Just "c_b") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8))))