module Biobase.Types.Location where
import Control.Lens hiding (Index, index)
import GHC.Generics (Generic)
import GHC.TypeNats
import Prelude hiding (length)
import Biobase.Types.Index
import Biobase.Types.Strand
data Location = Location
{ _lStrand ∷ !Strand
, _lStart ∷ !(Index 0)
, _lLength ∷ !Int
, _lTotalLength ∷ !Int
} deriving (Eq,Ord,Read,Show,Generic)
makeLenses ''Location
makePrisms ''Location
instance Reversing Location where
{-# Inline reversing #-}
reversing = undefined
startEndInclusive ∷ (KnownNat k) ⇒ Iso' Location (Strand, (Index k, Index k), Int)
{-# Inline startEndInclusive #-}
startEndInclusive = iso l2r r2l
where l2r z = let s = z^.lStrand; f = z^.lStart; l = z^.lLength
in (s, (reIndex f, reIndex $ f +. l -. 1), z^.lTotalLength)
r2l (s,(f,t),ttl) = Location s (reIndex f) (delta f t + 1) ttl
data PartialLocation
= PartialLocation
{ _plStrand ∷ !Strand
, _plStart ∷ !(Index 0)
, _plLength ∷ !Int
}
| ReversedPartialLocation
{ _plStrand ∷ !Strand
, _plEnd ∷ !(Index 0)
, _plLength ∷ !Int
}
deriving (Eq,Ord,Read,Show,Generic)
makeLenses ''PartialLocation
makePrisms ''PartialLocation
instance Reversing PartialLocation where
{-# Inline reversing #-}
reversing = \case
PartialLocation s t l → ReversedPartialLocation (s^.reversed) t l
locationPartial ∷ Iso' Location (PartialLocation,Int)
{-# Inline locationPartial #-}
locationPartial = iso l2r r2l where
l2r l = (PartialLocation (view lStrand l) (view lStart l) (view lLength l), l^.lTotalLength)
r2l (p,z) = case p of PartialLocation s t l → Location s t l z
ReversedPartialLocation s e l
| s `elem` [PlusStrand,MinusStrand] → Location s (index $ z- getIndex e -l) l z
| otherwise → Location s e l z