Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- readRawIpeFile :: (Coordinate r, Eq r) => FilePath -> IO (Either ConversionError (IpeFile r))
- readIpeFile :: (Coordinate r, Eq r) => FilePath -> IO (Either ConversionError (IpeFile r))
- readSinglePageFile :: (Coordinate r, Eq r) => FilePath -> IO (Either ConversionError (IpePage r))
- type ConversionError = Text
- fromIpeXML :: IpeRead (t r) => ByteString -> Either ConversionError (t r)
- readXML :: ByteString -> Either ConversionError (Node Text Text)
- class IpeReadText t where
- ipeReadText :: Text -> Either ConversionError t
- class IpeRead t where
- class IpeReadAttr t where
- ipeReadAttr :: Text -> Node Text Text -> Either ConversionError t
- ipeReadTextWith :: (Text -> Either t v) -> Text -> Either ConversionError (IpeValue v)
- ipeReadObject :: (IpeRead (i r), f ~ AttrMapSym1 r, ats ~ AttributesOf i, RecApplicative ats, ReifyConstraint IpeReadAttr (Attr f) ats, RecAll (Attr f) ats IpeReadAttr, AllConstrained IpeAttrName ats) => Proxy i -> proxy r -> Node Text Text -> Either ConversionError (i r :+ IpeAttributes i r)
- ipeReadAttrs :: forall proxy proxy' i r f ats. (f ~ AttrMapSym1 r, ats ~ AttributesOf i, ReifyConstraint IpeReadAttr (Attr f) ats, RecApplicative ats, RecAll (Attr f) ats IpeReadAttr, AllConstrained IpeAttrName ats) => proxy i -> proxy' r -> Node Text Text -> Either ConversionError (IpeAttributes i r)
- ipeReadRec :: forall f ats. (RecApplicative ats, ReifyConstraint IpeReadAttr (Attr f) ats, RecAll (Attr f) ats IpeReadAttr, AllConstrained IpeAttrName ats) => Proxy f -> Proxy ats -> Node Text Text -> Either ConversionError (Rec (Attr f) ats)
- class Fractional r => Coordinate r where
Reading ipe Files
readRawIpeFile :: (Coordinate r, Eq r) => FilePath -> IO (Either ConversionError (IpeFile r)) Source #
Given a file path, tries to read an ipe file
readIpeFile :: (Coordinate r, Eq r) => FilePath -> IO (Either ConversionError (IpeFile r)) Source #
Given a file path, tries to read an ipe file.
This function applies all matrices to objects.
readSinglePageFile :: (Coordinate r, Eq r) => FilePath -> IO (Either ConversionError (IpePage r)) Source #
Since most Ipe file contain only one page, we provide a shortcut for that as well.
This function applies all matrices, and it makes sure there is at least one layer and view in the page.
type ConversionError = Text Source #
Reading XML directly
fromIpeXML :: IpeRead (t r) => ByteString -> Either ConversionError (t r) Source #
Given a Bytestring, try to parse the bytestring into anything that is IpeReadable, i.e. any of the Ipe elements.
readXML :: ByteString -> Either ConversionError (Node Text Text) Source #
Reads the data from a Bytestring into a proper Node
Read classes
class IpeReadText t where Source #
Reading an ipe elemtn from a Text value
ipeReadText :: Text -> Either ConversionError t Source #
Instances
class IpeRead t where Source #
Reading an ipe lement from Xml
Instances
IpeRead LayerName Source # | |
Defined in Data.Geometry.Ipe.Reader | |
IpeRead View Source # | |
Defined in Data.Geometry.Ipe.Reader | |
(Coordinate r, Eq r) => IpeRead (Path r) Source # | |
Defined in Data.Geometry.Ipe.Reader | |
Coordinate r => IpeRead (Image r) Source # | |
Defined in Data.Geometry.Ipe.Reader | |
Coordinate r => IpeRead (IpeSymbol r) Source # | Ipe read instances |
Defined in Data.Geometry.Ipe.Reader | |
Coordinate r => IpeRead (MiniPage r) Source # | |
Defined in Data.Geometry.Ipe.Reader | |
Coordinate r => IpeRead (TextLabel r) Source # | |
Defined in Data.Geometry.Ipe.Reader | |
(Coordinate r, Eq r) => IpeRead (IpeObject r) Source # | |
Defined in Data.Geometry.Ipe.Reader | |
(Coordinate r, Eq r) => IpeRead (Group r) Source # | |
Defined in Data.Geometry.Ipe.Reader | |
(Coordinate r, Eq r) => IpeRead (IpePage r) Source # | |
Defined in Data.Geometry.Ipe.Reader | |
(Coordinate r, Eq r) => IpeRead (IpeFile r) Source # | |
Defined in Data.Geometry.Ipe.Reader |
class IpeReadAttr t where Source #
Basically IpeReadText for attributes. This class is not really meant to be
implemented directly. Just define an IpeReadText instance for the type
(Apply f at), then the generic instance below takes care of looking up the
name of the attribute, and calling the right ipeReadText value. This class
is just so that reifyConstraint in ipeReadRec
can select the right
typeclass when building the rec.
ipeReadAttr :: Text -> Node Text Text -> Either ConversionError t Source #
Instances
IpeReadText (Apply f at) => IpeReadAttr (Attr f at) Source # | |
Defined in Data.Geometry.Ipe.Reader ipeReadAttr :: Text -> Node Text Text -> Either ConversionError (Attr f at) Source # |
Some low level implementation functions
ipeReadTextWith :: (Text -> Either t v) -> Text -> Either ConversionError (IpeValue v) Source #
ipeReadObject :: (IpeRead (i r), f ~ AttrMapSym1 r, ats ~ AttributesOf i, RecApplicative ats, ReifyConstraint IpeReadAttr (Attr f) ats, RecAll (Attr f) ats IpeReadAttr, AllConstrained IpeAttrName ats) => Proxy i -> proxy r -> Node Text Text -> Either ConversionError (i r :+ IpeAttributes i r) Source #
If we can ipeRead an ipe element, and we can ipeReadAttrs its attributes we can properly read an ipe object using ipeReadObject
ipeReadAttrs :: forall proxy proxy' i r f ats. (f ~ AttrMapSym1 r, ats ~ AttributesOf i, ReifyConstraint IpeReadAttr (Attr f) ats, RecApplicative ats, RecAll (Attr f) ats IpeReadAttr, AllConstrained IpeAttrName ats) => proxy i -> proxy' r -> Node Text Text -> Either ConversionError (IpeAttributes i r) Source #
Reader for records. Given a proxy of some ipe type i, and a proxy of an coordinate type r, read the IpeAttributes for i from the xml node.
ipeReadRec :: forall f ats. (RecApplicative ats, ReifyConstraint IpeReadAttr (Attr f) ats, RecAll (Attr f) ats IpeReadAttr, AllConstrained IpeAttrName ats) => Proxy f -> Proxy ats -> Node Text Text -> Either ConversionError (Rec (Attr f) ats) Source #
Reading the Attributes into a Rec (Attr f), all based on the types of f (the type family mapping labels to types), and a list of labels (ats).
class Fractional r => Coordinate r where Source #
Represent stuff that can be used as a coordinate in ipe. (similar to show/read)
Nothing
fromSeq :: Integer -> Maybe (Int, Integer) -> r Source #
fromSeq :: (Ord r, Fractional r) => Integer -> Maybe (Int, Integer) -> r Source #
Instances
Coordinate Double Source # | |
Coordinate Float Source # | |
Coordinate (Ratio Integer) Source # | |
Coordinate (RealNumber p) Source # | |
Defined in Data.Geometry.Ipe.PathParser |