{-# LANGUAGE UnboxedTuples, MagicHash, RecordWildCards #-}
{-|
Module      : Parsley.Internal.Backend.Machine.Types.Input
Description : Packaging of offsets and positions.
License     : BSD-3-Clause
Maintainer  : Jamie Willis
Stability   : experimental

Exposes abstractions for working with combined offset and position information. `Input` is used
for static augmented information, and `Input#` is a raw combination of the two components.

@since 1.8.0.0
-}
module Parsley.Internal.Backend.Machine.Types.Input (
    Input(off), Input#(..),
    mkInput, fromInput, toInput,
    consume,
    forcePos, updatePos,
    chooseInput
  ) where

import Parsley.Internal.Backend.Machine.InputRep                  (Rep)
import Parsley.Internal.Backend.Machine.Types.Input.Offset        (Offset(offset), mkOffset, moveOne, moveN)
import Parsley.Internal.Backend.Machine.Types.Input.Pos           (StaPos, DynPos, toDynPos, fromDynPos, fromStaPos, force, update)
import Parsley.Internal.Backend.Machine.Types.InputCharacteristic (InputCharacteristic(..))
import Parsley.Internal.Common.Utils                              (Code)
import Parsley.Internal.Core.CharPred                             (CharPred)
import Parsley.Internal.Core.CombinatorAST                        (PosSelector)

{-|
Packages known static information about offsets (via `Offset`) with static information about positions
(currently unavailable).

@since 2.1.0.0
-}
data Input o = Input {
    -- | The offset contained within the input
    Input o -> Offset o
off  :: !(Offset o),
    -- | The position contained within the input
    Input o -> StaPos
pos :: !StaPos
  }

{-|
Packages a dynamic offset with a dynamic position.

@since 1.8.0.0
-}
data Input# o = Input# {
    Input# o -> Code (Rep o)
off#  :: !(Code (Rep o)),
    Input# o -> DynPos
pos#  :: !DynPos
  }

{-|
Constructs an `Input` given a dynamic offset and a static position.

@since 2.1.0.0
-}
mkInput :: Code (Rep o) -> (Word, Word) -> Input o
mkInput :: Code (Rep o) -> (Word, Word) -> Input o
mkInput Code (Rep o)
off = Offset o -> StaPos -> Input o
forall o. Offset o -> StaPos -> Input o
Input (Code (Rep o) -> Word -> Offset o
forall o. Code (Rep o) -> Word -> Offset o
mkOffset Code (Rep o)
off Word
0) (StaPos -> Input o)
-> ((Word, Word) -> StaPos) -> (Word, Word) -> Input o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word, Word) -> StaPos
fromStaPos

{-|
Strips away static information, returning the raw dynamic components.

@since 1.8.0.0
-}
fromInput :: Input o -> Input# o
fromInput :: Input o -> Input# o
fromInput Input{Offset o
StaPos
pos :: StaPos
off :: Offset o
pos :: forall o. Input o -> StaPos
off :: forall o. Input o -> Offset o
..} = Code (Rep o) -> DynPos -> Input# o
forall o. Code (Rep o) -> DynPos -> Input# o
Input# (Offset o -> Code (Rep o)
forall o. Offset o -> Code (Rep o)
offset Offset o
off) (StaPos -> DynPos
toDynPos StaPos
pos)

{-|
Given a unique identifier, forms a plainly annotated static combination of position and offset.

@since 1.8.0.0
-}
toInput :: Word -> Input# o -> Input o
toInput :: Word -> Input# o -> Input o
toInput Word
u Input#{DynPos
Code (Rep o)
pos# :: DynPos
off# :: Code (Rep o)
pos# :: forall o. Input# o -> DynPos
off# :: forall o. Input# o -> Code (Rep o)
..} = Offset o -> StaPos -> Input o
forall o. Offset o -> StaPos -> Input o
Input (Code (Rep o) -> Word -> Offset o
forall o. Code (Rep o) -> Word -> Offset o
mkOffset Code (Rep o)
off# Word
u) (DynPos -> StaPos
fromDynPos DynPos
pos#)

{-|
Register that a character has been consumed on this input, incorporating the new dynamic offset.

@since 2.1.0.0
-}
consume :: Code (Rep o) -> Input o -> Input o
consume :: Code (Rep o) -> Input o -> Input o
consume Code (Rep o)
offset' Input o
input = Input o
input {
    off :: Offset o
off = Offset o -> Code (Rep o) -> Offset o
forall o. Offset o -> Code (Rep o) -> Offset o
moveOne (Input o -> Offset o
forall o. Input o -> Offset o
off Input o
input) Code (Rep o)
offset'
  }

{-|
Collapse the position stored inside the input applying all updates to it. Once this has been completed,
the given `PosSelector` will be used to extract one of the line or column and return it to the given
continuation, along with the updated input post-collapse.

@since 2.1.0.0
-}
forcePos :: Input o -> PosSelector -> (Code Int -> Input o -> Code r) -> Code r
forcePos :: Input o -> PosSelector -> (Code Int -> Input o -> Code r) -> Code r
forcePos Input o
input PosSelector
sel Code Int -> Input o -> Code r
k = StaPos -> PosSelector -> (Code Int -> StaPos -> Code r) -> Code r
forall r.
StaPos -> PosSelector -> (Code Int -> StaPos -> Code r) -> Code r
force (Input o -> StaPos
forall o. Input o -> StaPos
pos Input o
input) PosSelector
sel (\Code Int
dp StaPos
sp -> Code Int -> Input o -> Code r
k Code Int
dp (Input o
input { pos :: StaPos
pos = StaPos
sp }))

{-|
Updates the position within the `Input` when a character has been consumed, providing it the
dynamic character that was produced as well as the static character-predicate that guarded it.

@since 2.1.0.0
-}
updatePos :: Input o -> Code Char -> CharPred -> Input o
updatePos :: Input o -> Code Char -> CharPred -> Input o
updatePos Input o
input Code Char
c CharPred
p = Input o
input { pos :: StaPos
pos = StaPos -> Code Char -> CharPred -> StaPos
update (Input o -> StaPos
forall o. Input o -> StaPos
pos Input o
input) Code Char
c CharPred
p }

{-|
Given knowledge about how input has been consumed through a call boundary, this function can update
the input using statically acquired knowledge.

@since 2.1.0.0
-}
-- TODO: In future, we could adjust InputCharacteristic to provide information about the static behaviours of the positions too...
chooseInput :: InputCharacteristic -> Word -> Input o -> Input# o -> Input o
chooseInput :: InputCharacteristic -> Word -> Input o -> Input# o -> Input o
chooseInput (AlwaysConsumes Maybe Word
n) Word
_ Input o
inp  Input# o
inp#  = Input o
inp { off :: Offset o
off = Maybe Word -> Offset o -> Code (Rep o) -> Offset o
forall o. Maybe Word -> Offset o -> Code (Rep o) -> Offset o
moveN Maybe Word
n (Input o -> Offset o
forall o. Input o -> Offset o
off Input o
inp) (Input# o -> Code (Rep o)
forall o. Input# o -> Code (Rep o)
off# Input# o
inp#), pos :: StaPos
pos = DynPos -> StaPos
fromDynPos (Input# o -> DynPos
forall o. Input# o -> DynPos
pos# Input# o
inp#) }
-- Technically, in this case, we know the whole input is unchanged. This essentially ignores the continuation arguments
-- hopefully GHC could optimise this better?
chooseInput InputCharacteristic
NeverConsumes      Word
_ Input o
inp  Input# o
_inp# = Input o
inp -- { off = (off inp) {offset = off# inp# }, pos = pos# inp# }
chooseInput InputCharacteristic
MayConsume         Word
u Input o
_inp Input# o
inp#  = Word -> Input# o -> Input o
forall o. Word -> Input# o -> Input o
toInput Word
u Input# o
inp#