module Database.Relational.Query.Pi.Unsafe (
Pi,
pfmap, pap,
width,
(<.>), (<?.>), (<?.?>),
pi,
definePi, defineDirectPi', defineDirectPi,
unsafeExpandIndexes
) where
import Prelude hiding (pi)
import Data.Array (listArray, (!))
import Database.Record.Persistable
(PersistableRecordWidth, runPersistableRecordWidth, unsafePersistableRecordWidth, (<&>),
PersistableWidth (persistableWidth), maybeWidth)
import Database.Relational.Query.Pure (ProductConstructor (..))
data Pi' r0 r1 = Leftest Int
| Map [Int]
unsafePiAppend' :: Pi' a b' -> Pi' b c' -> Pi' a c
unsafePiAppend' = d where
d (Leftest i) (Leftest j) = Leftest $ i + j
d (Leftest i) (Map js) = Map $ map (i +) js
d (Map is) (Leftest j) = Map $ drop j is
d (Map is) (Map js) = Map [ is' ! j | j <- js ] where
is' = listArray (0, length is) is
data Pi r0 r1 = Pi (Pi' r0 r1) (PersistableRecordWidth r1)
unsafePiAppend :: (PersistableRecordWidth c' -> PersistableRecordWidth c)
-> Pi a b' -> Pi b c' -> Pi a c
unsafePiAppend f (Pi p0 _) (Pi p1 w) =
Pi (p0 `unsafePiAppend'` p1) (f w)
unsafeExpandIndexes :: Pi a b -> [Int]
unsafeExpandIndexes = d where
d (Pi (Map is) _) = is
d (Pi (Leftest i) w) = [ i .. i + w' 1 ] where
w' = runPersistableRecordWidth w
unsafeCastRecordWidth :: PersistableRecordWidth a -> PersistableRecordWidth a'
unsafeCastRecordWidth = unsafePersistableRecordWidth . runPersistableRecordWidth
unsafeCast :: Pi a b' -> Pi a b
unsafeCast = c where
d (Leftest i) = Leftest i
d (Map m) = Map m
c (Pi p w) = Pi (d p) (unsafeCastRecordWidth w)
pfmap :: ProductConstructor (a -> b)
=> (a -> b) -> Pi r a -> Pi r b
_ `pfmap` p = unsafeCast p
pap :: Pi r (a -> b) -> Pi r a -> Pi r b
pap b@(Pi _ wb) c@(Pi _ wc) =
Pi
(Map $ unsafeExpandIndexes b ++ unsafeExpandIndexes c)
(unsafeCastRecordWidth $ wb <&> wc)
width' :: Pi r ct -> PersistableRecordWidth ct
width' (Pi _ w) = w
width :: Pi r a -> Int
width = runPersistableRecordWidth . width'
(<.>) :: Pi a b -> Pi b c -> Pi a c
(<.>) = unsafePiAppend id
(<?.>) :: Pi a (Maybe b) -> Pi b c -> Pi a (Maybe c)
(<?.>) = unsafePiAppend maybeWidth
(<?.?>) :: Pi a (Maybe b) -> Pi b (Maybe c) -> Pi a (Maybe c)
(<?.?>) = unsafePiAppend id
infixl 8 <.>, <?.>, <?.?>
pi :: [a] -> Pi r0 r1 -> [a]
pi cs (Pi p' w) = d p' where
d (Leftest i) = take (runPersistableRecordWidth w) . drop i $ cs
d (Map is) = [cs' ! i | i <- is]
cs' = listArray (0, length cs) cs
definePi' :: PersistableRecordWidth r1
-> Int
-> Pi r0 r1
definePi' pw i = Pi (Leftest i) pw
definePi :: PersistableWidth r1
=> Int
-> Pi r0 r1
definePi = definePi' persistableWidth
defineDirectPi' :: PersistableRecordWidth r1
-> [Int]
-> Pi r0 r1
defineDirectPi' pw is = Pi (Map is) pw
defineDirectPi :: PersistableWidth r1
=> [Int]
-> Pi r0 r1
defineDirectPi = defineDirectPi' persistableWidth