| Portability | portable |
|---|---|
| Stability | experimental |
| Maintainer | Edward L. Blake <edwardlblake@gmail.com> |
| Safe Haskell | Safe-Inferred |
Data.PHPSession
Contents
Description
Encodes and decodes serialized PHP sessions in the format used by the "php" setting for session.serialize_handler, as well as encodes and decodes PHP values in general in the format used by PHP's serialize/unserialize.
An example of using decodePHPSessionValue and convFrom to decode and convert values
from the serialized contents of a ByteString to [(:
Int,ByteString)]
import qualified Data.PHPSession as PHPSess
getArrayValues :: LBS.ByteString -> [(Int, LBS.ByteString)]
getArrayValues encoded =
case PHPSess.decodePHPSessionValue encoded of
Nothing -> [] :: [(Int,LBS.ByteString)]
Just b -> PHPSess.convFrom b
Starting from a value output from the following PHP code:
<?php echo serialize(array(0 => 'Hello', 5 => 'World'));
/* Outputs: "a:2:{i:0;s:5:\"Hello\";i:5;s:5:\"World\";}" */
The following can be computed:
>>>getArrayValues $ LBS.pack "a:2:{i:0;s:5:\"Hello\";i:5;s:5:\"World\";}"[(0,"Hello"),(5,"World")]
- decodePHPSession :: ByteString -> Maybe PHPSessionVariableList
- decodePHPSessionEither :: ByteString -> Either PHPSessionDecodingError PHPSessionVariableList
- decodePHPSessionValue :: ByteString -> Maybe PHPSessionValue
- decodePHPSessionValueEither :: ByteString -> Either PHPSessionDecodingError PHPSessionValue
- encodePHPSession :: PHPSessionVariableList -> ByteString
- encodePHPSessionValue :: PHPSessionValue -> ByteString
- convTo :: ConversionToPHPValue a => a -> PHPSessionValue
- convFrom :: ConversionFromPHPValueOrMismatch b => PHPSessionValue -> b
- convFromSafe :: ConversionFromPHPValueOrMismatch b => PHPSessionValue -> Either String b
- decodePartialPHPSessionValue :: ByteString -> Maybe (PHPSessionValue, ByteString)
- decodePartialPHPSessionValueEither :: ByteString -> Either PHPSessionDecodingError (PHPSessionValue, ByteString)
- type PHPSessionVariableList = [(ByteString, PHPSessionValue)]
- data PHPSessionClassName = PHPSessionClassName ByteString
- data PHPSessionValue
- = PHPSessionValueArray [(PHPSessionValue, PHPSessionValue)]
- | PHPSessionValueBool Bool
- | PHPSessionValueFloat (Either Int Double)
- | PHPSessionValueInt Int
- | PHPSessionValueNull
- | PHPSessionValueObject PHPSessionClassName [(PHPSessionValue, PHPSessionValue)]
- | PHPSessionValueObjectSerializeable PHPSessionClassName ByteString
- | PHPSessionValueString ByteString
- | PHPSessionValueMisc ByteString [PHPSessionAttr]
- data PHPSessionAttr
- = PHPSessionAttrInt Int
- | PHPSessionAttrFloat Double
- | PHPSessionAttrNested [PHPSessionValue]
Decode from ByteString
decodePHPSession :: ByteString -> Maybe PHPSessionVariableListSource
Decodes a ByteString containing a serialization of a list of session variables
using the "php" session serialization format into a PHPSessionVariableList
decodePHPSessionEither :: ByteString -> Either PHPSessionDecodingError PHPSessionVariableListSource
A version of decodePHPSession that returns a PHPSessionDecodingError when
decoding the ByteString fails.
decodePHPSessionValue :: ByteString -> Maybe PHPSessionValueSource
Decodes a ByteString containing a session serialization of a value into a
PHPSessionValue. The format being decoded is similar if not probably the same
format used by PHP's serialize/unserialize functions.
Nothing is returned if the input bytestring could not be parsed correctly.
decodePHPSessionValueEither :: ByteString -> Either PHPSessionDecodingError PHPSessionValueSource
A version of decodePHPSessionValue that returns PHPSessionDecodingError
when decoding the ByteString fails.
Encode to ByteString
encodePHPSession :: PHPSessionVariableList -> ByteStringSource
Encode a PHPSessionVariableList into a ByteString containing the serialization
of a list of session variables using the "php" session serialization format.
encodePHPSessionValue :: PHPSessionValue -> ByteStringSource
Encode a PHPSessionValue into a ByteString containing the serialization of a
PHP value. The format being encoded into is similar if not probably the same
format used by PHP's serialize/unserialize functions.
Convert to PHPSessionValue
convTo :: ConversionToPHPValue a => a -> PHPSessionValueSource
convTo is a convenience function that converts natively typed
values to PHPSessionValue, with the resulting PHP type determined
by the type cast or inferred.
arrayOfPHPStrings :: PHPSessionValue
arrayOfPHPStrings =
let str1 = "Hello" :: BS.ByteString
str2 = "World"
in convTo [(0 :: Int, str1), (1, str2)]
In the above example code, the OverloadedStrings language extension is assumed.
Convert from PHPSessionValue
convFrom :: ConversionFromPHPValueOrMismatch b => PHPSessionValue -> bSource
convFrom and convFromSafe are convenience functions that translate PHP
values stored as PHPSessionValue into appropriate Haskell types depending on
the desired type cast or inferred. Functions provided in this module provide
non-coerced type translations and so will either carry on the translation or
signal the fact that the attempted conversion will alter the type of the
value. For situations where altering value types is expected, alternative
conversion functions with similar type signatures are provided in modules
within Data.PHPSession.ImplicitConv.
The example arrayOfPHPStrings definition given in convTo can be reverted back
to Haskell types, which evaluates to [(0,"Hello"),(1,"World")].
>>>convFrom arrayOfPHPStrings :: [(Int,LBS.ByteString)][(0,"Hello"),(1,"World")]
However, if the desired type signature is changed to a completely different type, then a runtime exception is thrown:
>>>convFrom arrayOfPHPStrings :: [(Int,Int)]*** Exception: Type mismatch converting from (PHPSessionValueString "Hello") to Int
Where there is the possibility that the value being sought may be NULL, the
type should be (.
Maybe a)
convFromSafe :: ConversionFromPHPValueOrMismatch b => PHPSessionValue -> Either String bSource
A version of convFrom which returns a Left with an error message instead
of throwing an exception.
Decode only part of a ByteString
decodePartialPHPSessionValue :: ByteString -> Maybe (PHPSessionValue, ByteString)Source
Decodes as much of a ByteString as needed into a PHPSessionValue and returns
the rest of the string. Decoding ends at either the end of the string or when the
extent of the current nested structure is met when an extra closing curly brace is
encountered. The format being decoded is similar if not probably the same
format used by PHP's serialize/unserialize functions.
Nothing is returned if the input bytestring could not be parsed correctly.
decodePartialPHPSessionValueEither :: ByteString -> Either PHPSessionDecodingError (PHPSessionValue, ByteString)Source
A version of decodePartialPHPSessionValue that uses Either, on decoding error a
PHPSessionDecodingError is returned.
PHP session types
type PHPSessionVariableList = [(ByteString, PHPSessionValue)]Source
Holds the "top-level" session variables and their value contents.
data PHPSessionClassName Source
Represents the name of a PHP class.
Constructors
| PHPSessionClassName ByteString |
Instances
data PHPSessionValue Source
PHPSessionValue Represents a PHP value, which may be a number, string,
array, object, boolean, null, or references.
-
PHPSessionValueArrayrepresents an array as a list of key-value pairs of values of typePHPSessionValue. -
PHPSessionValueObjectis similar toPHPSessionValueArraybut also includes a class name of typePHPSessionClassName. -
PHPSessionValueObjectSerializeablerepresent objects of which their classes implement Serializeable to handle their own serialization and don't use the normal serialization format for its contained objects. -
PHPSessionValueBool,PHPSessionValueInt,PHPSessionValueFloat,PHPSessionValueNull, andPHPSessionValueStringrepresent basic types boolean, integer, floats, null and string respectively. -
PHPSessionValueFloatstores the number representation as anEitherIntDoubleto preserve instances where the number representation is actually an integer. It should be noted that the re-encoded value is usually rounded unlike PHP's representation. -
PHPSessionValueMiscstores a few other types such as references and values which follow the general serialization format but aren't recognized by the decoder. A list ofPHPSessionAttrprovides the information for reconstructing the serialized representation when re-encoding this type of value.
Constructors
| PHPSessionValueArray [(PHPSessionValue, PHPSessionValue)] | |
| PHPSessionValueBool Bool | |
| PHPSessionValueFloat (Either Int Double) | |
| PHPSessionValueInt Int | |
| PHPSessionValueNull | |
| PHPSessionValueObject PHPSessionClassName [(PHPSessionValue, PHPSessionValue)] | |
| PHPSessionValueObjectSerializeable PHPSessionClassName ByteString | |
| PHPSessionValueString ByteString | |
| PHPSessionValueMisc ByteString [PHPSessionAttr] |
Instances
data PHPSessionAttr Source
PHPSessionAttr are values associated with PHPSessionValueMisc to inspect and
generally re-encode the necessary information for that value.
Constructors
| PHPSessionAttrInt Int | |
| PHPSessionAttrFloat Double | |
| PHPSessionAttrNested [PHPSessionValue] |
Instances
| Eq PHPSessionAttr | |
| Show PHPSessionAttr |