gtvm-hs-1.0.0: Various tools for reversing and using assets from Golden Time: Vivid Memories.
Safe HaskellNone
LanguageGHC2021

GTVM.Studio

Synopsis

Documentation

newtype ScpId Source #

Constructors

ScpId 

Fields

Instances

Instances details
IsString ScpId Source # 
Instance details

Defined in GTVM.Studio

Methods

fromString :: String -> ScpId #

Show ScpId Source # 
Instance details

Defined in GTVM.Studio

Methods

showsPrec :: Int -> ScpId -> ShowS #

show :: ScpId -> String #

showList :: [ScpId] -> ShowS #

Eq ScpId Source # 
Instance details

Defined in GTVM.Studio

Methods

(==) :: ScpId -> ScpId -> Bool #

(/=) :: ScpId -> ScpId -> Bool #

type TLSeg' = TLSeg (Const () :: Type -> Type) Text Source #

Yes, we're ignoring the source fields. We'll fill them in during an export pass. Easier on the brain.

data Studio (m :: k) a where Source #

Constructors

WriteTl :: forall {k} (m :: k). TLSeg' -> Studio m () 
ReadTl 

Fields

JumpTlInit 

Fields

  • :: forall {k} (m :: k). Studio m ()

    Jump to the first translation target SCP command and reset.

NextTl 

Fields

  • :: forall {k} (m :: k). Studio m ()

    Step to the next translation target SCP command.

PrevTl 

Fields

  • :: forall {k} (m :: k). Studio m ()

    Step to the previous translation target SCP command.

LoadScp 

Fields

  • :: forall {k} (m :: k). ScpId
     
  • -> Studio m ()

    Load the requested SCP.

GenerateFreshScpTl 

Fields

  • :: forall {k} (m :: k). Path Rel Dir
     
  • -> Studio m ()

    Generate a fresh SCPTL for the currently loaded SCP and place in the the requested studio folder.

LoadScpTl 

Fields

  • :: forall {k} (m :: k). Path Rel Dir
     
  • -> Studio m ()

    Load the SCPTL for the currently loaded SCP, stored at the requested studio folder.

SaveScpTl 

Fields

  • :: forall {k} (m :: k). Path Rel Dir
     
  • -> Studio m ()

    Save the currently loaded SCPTL to disk.

writeTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => TLSeg' -> Sem r () Source #

readTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Sem r (Maybe TLSeg') Source #

jumpTlInit :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Sem r () Source #

nextTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Sem r () Source #

prevTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Sem r () Source #

loadScp :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => ScpId -> Sem r () Source #

generateFreshScpTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Path Rel Dir -> Sem r () Source #

loadScpTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Path Rel Dir -> Sem r () Source #

saveScpTl :: forall (r :: EffectRow). Member (Studio :: (Type -> Type) -> Type -> Type) r => Path Rel Dir -> Sem r () Source #

jumpTl :: forall (r :: EffectRow). Members '[Studio :: (Type -> Type) -> Type -> Type] r => Natural -> Sem r () Source #

Resets and steps to the translation target SCP command with the requested index.

TODO better behaviour if we jump too far (don't keep spamming nextTl)? but this should be prefaced with a UI check that the index exists

loadFreshScpTl :: forall (r :: EffectRow). Members '[Studio :: (Type -> Type) -> Type -> Type] r => Path Rel Dir -> Sem r () Source #

Generate a fresh SCPTL for the currently loaded SCP, place in the requested studio folder and load immediately.

data St Source #

Constructors

St 

Instances

Instances details
Generic St Source # 
Instance details

Defined in GTVM.Studio

Associated Types

type Rep St 
Instance details

Defined in GTVM.Studio

Methods

from :: St -> Rep St x #

to :: Rep St x -> St #

Show St Source # 
Instance details

Defined in GTVM.Studio

Methods

showsPrec :: Int -> St -> ShowS #

show :: St -> String #

showList :: [St] -> ShowS #

Eq St Source # 
Instance details

Defined in GTVM.Studio

Methods

(==) :: St -> St -> Bool #

(/=) :: St -> St -> Bool #

type Rep St Source # 
Instance details

Defined in GTVM.Studio

setAt :: Int -> a -> [a] -> [a] Source #

runStudio :: forall (r :: EffectRow) a. Members '[State St :: (Type -> Type) -> Type -> Type, Output Text :: (Type -> Type) -> Type -> Type, Embed IO] r => Path Abs Dir -> Sem ((Studio :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a Source #

scpPrevTlIdx :: forall (f :: Strength) a. SCP f a -> Int -> Maybe Int Source #

scpNextTlIdx :: forall (f :: Strength) a. SCP f a -> Int -> Either Int Int Source #

tlSegIsEmpty :: forall a (f :: Type -> Type). (Eq a, Monoid a) => TLSeg f a -> Bool Source #

studioLog :: forall (r :: EffectRow). Member (Output Text :: (Type -> Type) -> Type -> Type) r => Text -> Sem r () Source #

Required to avoid lots of type annotation, that's life Jim

runStudioLog :: forall (r :: EffectRow) o a. Member (Embed IO) r => (o -> IO ()) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a Source #

pLoadAndGenFirstScript :: forall (r :: EffectRow). Members '[Studio :: (Type -> Type) -> Type -> Type, Embed IO] r => Sem r () Source #

tlsegTextbox :: a -> TLSeg (Const () :: Type -> Type) a Source #