| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
LDtk
Synopsis
- loadLDtk :: FilePath -> IO (Either String LDtkRoot)
- data Field = Field {
- __identifier :: Text
- __tile :: Maybe TilesetRect
- __type :: Text
- __value :: FieldValue
- defUid :: Int
- data Entity = Entity {}
- data Tile = Tile {}
- data TilesetRect = TilesetRect {}
- data FieldValue
- data EntityReferenceInfos = EntityReferenceInfos {}
- data Flip
- data Pair a = Pair {}
- data GridPoint = GridPoint {}
- data Layer = Layer {
- __cHei :: Int
- __cWid :: Int
- __gridSize :: Int
- __identifier :: Text
- __opacity :: Float
- __pxTotalOffsetX :: Int
- __pxTotalOffsetY :: Int
- __tilesetDefUid :: Maybe Int
- __tilesetRelPath :: Maybe Text
- __type :: LayerType
- autoLayerTiles :: [Tile]
- entityInstances :: [Entity]
- gridTiles :: [Tile]
- iid :: Text
- intGridCsv :: [Int]
- layerDefUid :: Maybe Int
- tilesetRelPath :: Maybe Text
- levelId :: Int
- overrideTilesetUid :: Maybe Int
- visible :: Bool
- data Level = Level {}
- data Neighbour = Neighbour {}
- data Direction
- data BgPos = BgPos {}
- data Rect a = Rect {}
- data World = World {
- identifier :: Text
- iid :: Text
- levels :: [Level]
- worldGridHeight :: Maybe Int
- worldGridWidth :: Maybe Int
- worldLayout :: WorldLayout
- data LayerType
- data WorldLayout
- data TileRenderMode
- data LDtkRoot = LDtkRoot {
- bgColor :: Color
- defs :: Definitions
- externalLevels :: Bool
- iid :: Text
- jsonVersion :: Text
- levels :: [Level]
- worldGridHeight :: Maybe Int
- worldGridWidth :: Maybe Int
- worldLayout :: WorldLayout
- worlds :: [World]
- data LayerDef = LayerDef {
- __type :: LayerType
- autoSourceLayerDefUid :: Maybe Int
- displayOpacity :: Float
- gridSize :: Int
- identifier :: Text
- intGridValues :: [GridValue]
- parallaxFactorX :: Float
- parallaxFactorY :: Float
- parallaxScaling :: Bool
- pxOffsetX :: Int
- pxOffsetY :: Int
- tilesetDefUid :: Maybe Int
- uid :: Int
- data GridValue = GridValue {}
- data EnumDef = EnumDef {
- externalRelPath :: Maybe FilePath
- iconTilesetUid :: Maybe Int
- identifier :: Text
- tags :: [Text]
- uid :: Int
- values :: [EnumValueDef]
- data EnumValueDef = EnumValueDef {}
- data Definitions = Definitions {
- entities :: [EntityDef]
- enums :: [EnumDef]
- externalEnums :: [EnumDef]
- layers :: [LayerDef]
- tilesets :: [TilesetDef]
- data TilesetDef = TilesetDef {
- __cHei :: Int
- __cWid :: Int
- customData :: [CustomData]
- embedAtlas :: Maybe EmbedAtlas
- enumTags :: [EnumTag]
- identifier :: Text
- padding :: Int
- pxHei :: Int
- pxWid :: Int
- relPath :: Maybe FilePath
- spacing :: Int
- tags :: [Text]
- tagsSourceEnumUid :: Maybe Int
- tileGridSize :: Int
- uid :: Int
- data EnumTag = EnumTag {
- enumValueId :: Text
- tileIds :: [Int]
- data CustomData = CustomData {}
- data EmbedAtlas = LdtkIcons
- data EntityDef = EntityDef {
- color :: Color
- height :: Int
- identifier :: Text
- nineSliceBorders :: [Int]
- pivotX :: Float
- pivotY :: Float
- tileRect :: Maybe TilesetRect
- tileRenderMode :: TileRenderMode
- tilesetId :: Maybe Int
- uid :: Int
- width :: Int
- data Color = Color {}
Documentation
Constructors
| Field | |
Fields
| |
Instances
| Eq Field Source # | |
| Ord Field Source # | |
| Read Field Source # | |
| Show Field Source # | |
| Generic Field Source # | |
| FromJSON Field Source # | |
| type Rep Field Source # | |
Defined in LDtk.Types type Rep Field = D1 ('MetaData "Field" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "Field" 'PrefixI 'True) ((S1 ('MetaSel ('Just "__identifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "__tile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TilesetRect))) :*: (S1 ('MetaSel ('Just "__type") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "__value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FieldValue) :*: S1 ('MetaSel ('Just "defUid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) | |
Constructors
| Entity | |
Instances
Instances
| Eq Tile Source # | |
| Ord Tile Source # | |
| Read Tile Source # | |
| Show Tile Source # | |
| Generic Tile Source # | |
| FromJSON Tile Source # | |
| type Rep Tile Source # | |
Defined in LDtk.Types type Rep Tile = D1 ('MetaData "Tile" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "Tile" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tile_flip") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Flip) :*: S1 ('MetaSel ('Just "px") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pair Int))) :*: (S1 ('MetaSel ('Just "src") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pair Int)) :*: S1 ('MetaSel ('Just "t") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))) | |
data TilesetRect Source #
Instances
data FieldValue Source #
Constructors
Instances
data EntityReferenceInfos Source #
Constructors
| EntityReferenceInfos | |
Instances
Instances
| Bounded Flip Source # | |
| Enum Flip Source # | |
| Eq Flip Source # | |
| Ord Flip Source # | |
| Read Flip Source # | |
| Show Flip Source # | |
| Generic Flip Source # | |
| FromJSON Flip Source # | |
| type Rep Flip Source # | |
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))) | |
Instances
| Eq a => Eq (Pair a) Source # | |
| Ord a => Ord (Pair a) Source # | |
| Read a => Read (Pair a) Source # | |
| Show a => Show (Pair a) Source # | |
| Generic (Pair a) Source # | |
| FromJSON a => FromJSON (Pair a) Source # | |
| type Rep (Pair a) Source # | |
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))) | |
Instances
| Eq GridPoint Source # | |
| Ord GridPoint Source # | |
| Read GridPoint Source # | |
| Show GridPoint Source # | |
| Generic GridPoint Source # | |
| FromJSON GridPoint Source # | |
| type Rep GridPoint Source # | |
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))) | |
Constructors
| Layer | |
Fields
| |
Instances
Constructors
| Level | |
Instances
Instances
| Eq Neighbour Source # | |
| Ord Neighbour Source # | |
| Read Neighbour Source # | |
| Show Neighbour Source # | |
| Generic Neighbour Source # | |
| FromJSON Neighbour Source # | |
| type Rep Neighbour Source # | |
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))) | |
Instances
| Eq Direction Source # | |
| Ord Direction Source # | |
| Read Direction Source # | |
| Show Direction Source # | |
| Generic Direction Source # | |
| FromJSON Direction Source # | |
| type Rep Direction Source # | |
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))) | |
Instances
| Eq BgPos Source # | |
| Ord BgPos Source # | |
| Read BgPos Source # | |
| Show BgPos Source # | |
| Generic BgPos Source # | |
| FromJSON BgPos Source # | |
| type Rep BgPos Source # | |
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))))) | |
Instances
| Eq a => Eq (Rect a) Source # | |
| Ord a => Ord (Rect a) Source # | |
| Read a => Read (Rect a) Source # | |
| Show a => Show (Rect a) Source # | |
| Generic (Rect a) Source # | |
| FromJSON a => FromJSON (Rect a) Source # | |
| type Rep (Rect a) Source # | |
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)))) | |
Constructors
| World | |
Fields
| |
Instances
| Eq World Source # | |
| Ord World Source # | |
| Read World Source # | |
| Show World Source # | |
| Generic World Source # | |
| FromJSON World Source # | |
| type Rep World Source # | |
Defined in LDtk.Types type Rep World = D1 ('MetaData "World" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "World" 'PrefixI 'True) ((S1 ('MetaSel ('Just "identifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "iid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "levels") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Level]))) :*: (S1 ('MetaSel ('Just "worldGridHeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "worldGridWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "worldLayout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WorldLayout))))) | |
Instances
| Bounded LayerType Source # | |
| Enum LayerType Source # | |
Defined in LDtk.Types Methods succ :: LayerType -> LayerType # pred :: LayerType -> LayerType # fromEnum :: LayerType -> Int # enumFrom :: LayerType -> [LayerType] # enumFromThen :: LayerType -> LayerType -> [LayerType] # enumFromTo :: LayerType -> LayerType -> [LayerType] # enumFromThenTo :: LayerType -> LayerType -> LayerType -> [LayerType] # | |
| Eq LayerType Source # | |
| Ord LayerType Source # | |
| Read LayerType Source # | |
| Show LayerType Source # | |
| Generic LayerType Source # | |
| FromJSON LayerType Source # | |
| type Rep LayerType Source # | |
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 #
Constructors
| Free | |
| GridVania | |
| LinearHorizontal | |
| LinearVertical |
Instances
data TileRenderMode Source #
Constructors
| Cover | |
| FitInside | |
| Repeat | |
| Stretch | |
| FullSizeCropped | |
| FillSizeUncropped | |
| NineSlice |
Instances
Constructors
| LDtkRoot | |
Fields
| |
Instances
Constructors
| LayerDef | |
Fields
| |
Instances
Instances
| Eq GridValue Source # | |
| Ord GridValue Source # | |
| Read GridValue Source # | |
| Show GridValue Source # | |
| Generic GridValue Source # | |
| FromJSON GridValue Source # | |
| type Rep GridValue Source # | |
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)))) | |
Constructors
| EnumDef | |
Fields
| |
Instances
| Eq EnumDef Source # | |
| Ord EnumDef Source # | |
| Read EnumDef Source # | |
| Show EnumDef Source # | |
| Generic EnumDef Source # | |
| FromJSON EnumDef Source # | |
| type Rep EnumDef Source # | |
Defined in LDtk.Types type Rep EnumDef = D1 ('MetaData "EnumDef" "LDtk.Types" "ldtk-types-1.2.3-DZMGLHH7vdEG0gO9iOSohR" 'False) (C1 ('MetaCons "EnumDef" 'PrefixI 'True) ((S1 ('MetaSel ('Just "externalRelPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)) :*: (S1 ('MetaSel ('Just "iconTilesetUid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "identifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :*: (S1 ('MetaSel ('Just "tags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: (S1 ('MetaSel ('Just "uid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "values") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [EnumValueDef]))))) | |
data EnumValueDef Source #
Constructors
| EnumValueDef | |
Instances
data Definitions Source #
Constructors
| Definitions | |
Fields
| |
Instances
data TilesetDef Source #
Constructors
| TilesetDef | |
Fields
| |
Instances
Constructors
| EnumTag | |
Fields
| |
Instances
| Eq EnumTag Source # | |
| Ord EnumTag Source # | |
| Read EnumTag Source # | |
| Show EnumTag Source # | |
| Generic EnumTag Source # | |
| FromJSON EnumTag Source # | |
| type Rep EnumTag Source # | |
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 | |
Instances
data EmbedAtlas Source #
Constructors
| LdtkIcons |
Instances
Constructors
| EntityDef | |
Fields
| |
Instances
Instances
| Eq Color Source # | |
| Ord Color Source # | |
| Read Color Source # | |
| Show Color Source # | |
| Generic Color Source # | |
| FromJSON Color Source # | |
| type Rep Color Source # | |
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)))) | |