aeson-tiled-0.0.0.1: Aeson instances for the Tiled map editor.

Safe HaskellNone
LanguageHaskell2010

Data.Aeson.Tiled

Contents

Description

This module provides Haskell types for Tiled's JSON exports, which you can read about at http://doc.mapeditor.org/en/latest/reference/json-map-format/. That said - as of the writing of this module the JSON documentation does not cover some of the types and records that are available in the format. For those you should read the TMX documentation at http://doc.mapeditor.org/en/latest/reference/tmx-map-format/

Synopsis

Tiled map editor types, their aeson instances and map loading

newtype GlobalId Source #

A globally indexed identifier.

Constructors

GlobalId 

Fields

Instances

Enum GlobalId Source # 
Eq GlobalId Source # 
Num GlobalId Source # 
Ord GlobalId Source # 
Show GlobalId Source # 
Generic GlobalId Source # 

Associated Types

type Rep GlobalId :: * -> * #

Methods

from :: GlobalId -> Rep GlobalId x #

to :: Rep GlobalId x -> GlobalId #

FromJSON GlobalId Source # 
FromJSONKey GlobalId Source # 
ToJSON GlobalId Source # 
ToJSONKey GlobalId Source # 
type Rep GlobalId Source # 
type Rep GlobalId = D1 (MetaData "GlobalId" "Data.Aeson.Tiled" "aeson-tiled-0.0.0.1-8EMrN7jFZObCrz6NTOUtxy" True) (C1 (MetaCons "GlobalId" PrefixI True) (S1 (MetaSel (Just Symbol "unGlobalId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

newtype LocalId Source #

A locally indexed identifier.

Constructors

LocalId 

Fields

Instances

Enum LocalId Source # 
Eq LocalId Source # 

Methods

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

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

Num LocalId Source # 
Ord LocalId Source # 
Show LocalId Source # 
Generic LocalId Source # 

Associated Types

type Rep LocalId :: * -> * #

Methods

from :: LocalId -> Rep LocalId x #

to :: Rep LocalId x -> LocalId #

FromJSON LocalId Source # 
FromJSONKey LocalId Source # 
ToJSON LocalId Source # 
ToJSONKey LocalId Source # 
type Rep LocalId Source # 
type Rep LocalId = D1 (MetaData "LocalId" "Data.Aeson.Tiled" "aeson-tiled-0.0.0.1-8EMrN7jFZObCrz6NTOUtxy" True) (C1 (MetaCons "LocalId" PrefixI True) (S1 (MetaSel (Just Symbol "unLocalId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data Object Source #

Constructors

Object 

Fields

Instances

Eq Object Source # 

Methods

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

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

Show Object Source # 
Generic Object Source # 

Associated Types

type Rep Object :: * -> * #

Methods

from :: Object -> Rep Object x #

to :: Rep Object x -> Object #

FromJSON Object Source # 
ToJSON Object Source # 
type Rep Object Source # 
type Rep Object = D1 (MetaData "Object" "Data.Aeson.Tiled" "aeson-tiled-0.0.0.1-8EMrN7jFZObCrz6NTOUtxy" False) (C1 (MetaCons "Object" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "objectId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "objectWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "objectHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "objectName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "objectType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) ((:*:) (S1 (MetaSel (Just Symbol "objectProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Text Text))) (S1 (MetaSel (Just Symbol "objectVisible") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "objectX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "objectY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) ((:*:) (S1 (MetaSel (Just Symbol "objectRotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float)) (S1 (MetaSel (Just Symbol "objectGid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GlobalId)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "objectEllipse") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "objectPolygon") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector (Int, Int))))) ((:*:) (S1 (MetaSel (Just Symbol "objectPolyline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector (Int, Int)))) (S1 (MetaSel (Just Symbol "objectText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Text Text))))))))

data Layer Source #

Constructors

Layer 

Fields

Instances

Eq Layer Source # 

Methods

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

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

Show Layer Source # 

Methods

showsPrec :: Int -> Layer -> ShowS #

show :: Layer -> String #

showList :: [Layer] -> ShowS #

Generic Layer Source # 

Associated Types

type Rep Layer :: * -> * #

Methods

from :: Layer -> Rep Layer x #

to :: Rep Layer x -> Layer #

FromJSON Layer Source # 
ToJSON Layer Source # 
type Rep Layer Source # 
type Rep Layer = D1 (MetaData "Layer" "Data.Aeson.Tiled" "aeson-tiled-0.0.0.1-8EMrN7jFZObCrz6NTOUtxy" False) (C1 (MetaCons "Layer" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "layerWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "layerHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "layerName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:*:) (S1 (MetaSel (Just Symbol "layerType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "layerVisible") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "layerX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "layerY") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "layerData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Vector GlobalId)))) (S1 (MetaSel (Just Symbol "layerObjects") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Vector Object)))))) ((:*:) (S1 (MetaSel (Just Symbol "layerProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Text Text))) ((:*:) (S1 (MetaSel (Just Symbol "layerOpacity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float)) (S1 (MetaSel (Just Symbol "layerDraworder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))))

data Terrain Source #

Constructors

Terrain 

Fields

Instances

data Frame Source #

Constructors

Frame 

Instances

Eq Frame Source # 

Methods

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

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

Show Frame Source # 

Methods

showsPrec :: Int -> Frame -> ShowS #

show :: Frame -> String #

showList :: [Frame] -> ShowS #

Generic Frame Source # 

Associated Types

type Rep Frame :: * -> * #

Methods

from :: Frame -> Rep Frame x #

to :: Rep Frame x -> Frame #

FromJSON Frame Source # 
ToJSON Frame Source # 
type Rep Frame Source # 
type Rep Frame = D1 (MetaData "Frame" "Data.Aeson.Tiled" "aeson-tiled-0.0.0.1-8EMrN7jFZObCrz6NTOUtxy" False) (C1 (MetaCons "Frame" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "frameDuration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "frameTileId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LocalId))))

data Tile Source #

data Tileset Source #

Constructors

Tileset 

Fields

Instances

Eq Tileset Source # 

Methods

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

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

Show Tileset Source # 
Generic Tileset Source # 

Associated Types

type Rep Tileset :: * -> * #

Methods

from :: Tileset -> Rep Tileset x #

to :: Rep Tileset x -> Tileset #

FromJSON Tileset Source # 
ToJSON Tileset Source # 
type Rep Tileset Source # 
type Rep Tileset = D1 (MetaData "Tileset" "Data.Aeson.Tiled" "aeson-tiled-0.0.0.1-8EMrN7jFZObCrz6NTOUtxy" False) (C1 (MetaCons "Tileset" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "tilesetFirstgid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GlobalId)) (S1 (MetaSel (Just Symbol "tilesetImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) ((:*:) (S1 (MetaSel (Just Symbol "tilesetName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "tilesetTilewidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "tilesetTileheight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "tilesetImagewidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) ((:*:) (S1 (MetaSel (Just Symbol "tilesetImageheight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "tilesetProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Text Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "tilesetPropertytypes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Text Text))) (S1 (MetaSel (Just Symbol "tilesetMargin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) ((:*:) (S1 (MetaSel (Just Symbol "tilesetSpacing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "tilesetTileproperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map GlobalId (Map Text Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "tilesetTerrains") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector Terrain))) (S1 (MetaSel (Just Symbol "tilesetColumns") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) ((:*:) (S1 (MetaSel (Just Symbol "tilesetTilecount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "tilesetTiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map LocalId Tile))))))))

data Tiledmap Source #

The full monty.

Constructors

Tiledmap 

Fields

Instances

Eq Tiledmap Source # 
Show Tiledmap Source # 
Generic Tiledmap Source # 

Associated Types

type Rep Tiledmap :: * -> * #

Methods

from :: Tiledmap -> Rep Tiledmap x #

to :: Rep Tiledmap x -> Tiledmap #

FromJSON Tiledmap Source # 
ToJSON Tiledmap Source # 
type Rep Tiledmap Source # 
type Rep Tiledmap = D1 (MetaData "Tiledmap" "Data.Aeson.Tiled" "aeson-tiled-0.0.0.1-8EMrN7jFZObCrz6NTOUtxy" False) (C1 (MetaCons "Tiledmap" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "tiledmapVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float)) ((:*:) (S1 (MetaSel (Just Symbol "tiledmapTiledversion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "tiledmapWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) ((:*:) (S1 (MetaSel (Just Symbol "tiledmapHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "tiledmapTilewidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "tiledmapTileheight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "tiledmapOrientation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "tiledmapLayers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector Layer))) (S1 (MetaSel (Just Symbol "tiledmapTilesets") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector Tileset))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "tiledmapBackgroundcolor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) (S1 (MetaSel (Just Symbol "tiledmapRenderorder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) ((:*:) (S1 (MetaSel (Just Symbol "tiledmapProperties") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Text Text))) (S1 (MetaSel (Just Symbol "tiledmapNextobjectid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))))))

loadTiledmap :: FilePath -> IO (Either String Tiledmap) Source #

Load a Tiled map from the given FilePath.

Re-exports for working with Tiled types

module Data.Map