module Internal.Data.Basic.SqlToHsTypes where import Internal.Interlude import Prelude (lex) import Database.PostgreSQL.Simple.FromField import qualified Database.PostgreSQL.Simple.TypeInfo.Static as TypeId import qualified Data.ByteString.Char8 as B import Database.PostgreSQL.Simple.ToField import Data.Binary.Builder data Point = Point {-# UNPACK #-} !Double {-# UNPACK #-} !Double deriving (Eq, Ord, Read, Show) instance FromField Point where fromField f mdata = if typeOid f /= TypeId.typoid TypeId.point then returnError Incompatible f "" else case B.unpack <$> mdata of Nothing -> returnError UnexpectedNull f "" Just dat -> case [ x | (x,t) <- reads dat, ("","") <- lex t ] of [(x, y)] -> return (Point x y) _ -> returnError ConversionFailed f dat instance ToField Point where toField (Point x y) = Plain (fromByteString bs) where bs = "point(" <> show x <> ", " <> show y <> ")"