{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
module Langchain.PromptTemplate
(
PromptTemplate (..)
, FewShotPromptTemplate (..)
, renderPrompt
, renderFewShotPrompt
) where
import qualified Data.Map.Strict as HM
import Data.Text (Text)
import qualified Data.Text as T
import Langchain.Runnable.Core (Runnable (..))
newtype PromptTemplate = PromptTemplate
{ PromptTemplate -> Text
templateString :: Text
}
deriving (Int -> PromptTemplate -> ShowS
[PromptTemplate] -> ShowS
PromptTemplate -> String
(Int -> PromptTemplate -> ShowS)
-> (PromptTemplate -> String)
-> ([PromptTemplate] -> ShowS)
-> Show PromptTemplate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PromptTemplate -> ShowS
showsPrec :: Int -> PromptTemplate -> ShowS
$cshow :: PromptTemplate -> String
show :: PromptTemplate -> String
$cshowList :: [PromptTemplate] -> ShowS
showList :: [PromptTemplate] -> ShowS
Show, PromptTemplate -> PromptTemplate -> Bool
(PromptTemplate -> PromptTemplate -> Bool)
-> (PromptTemplate -> PromptTemplate -> Bool) -> Eq PromptTemplate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PromptTemplate -> PromptTemplate -> Bool
== :: PromptTemplate -> PromptTemplate -> Bool
$c/= :: PromptTemplate -> PromptTemplate -> Bool
/= :: PromptTemplate -> PromptTemplate -> Bool
Eq)
renderPrompt :: PromptTemplate -> HM.Map Text Text -> Either String Text
renderPrompt :: PromptTemplate -> Map Text Text -> Either String Text
renderPrompt (PromptTemplate Text
template) Map Text Text
vars = Map Text Text -> Text -> Either String Text
interpolate Map Text Text
vars Text
template
data FewShotPromptTemplate = FewShotPromptTemplate
{ FewShotPromptTemplate -> Text
fsPrefix :: Text
, FewShotPromptTemplate -> [Map Text Text]
fsExamples :: [HM.Map Text Text]
, FewShotPromptTemplate -> Text
fsExampleTemplate :: Text
, FewShotPromptTemplate -> Text
fsExampleSeparator :: Text
, FewShotPromptTemplate -> Text
fsSuffix :: Text
}
deriving (Int -> FewShotPromptTemplate -> ShowS
[FewShotPromptTemplate] -> ShowS
FewShotPromptTemplate -> String
(Int -> FewShotPromptTemplate -> ShowS)
-> (FewShotPromptTemplate -> String)
-> ([FewShotPromptTemplate] -> ShowS)
-> Show FewShotPromptTemplate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FewShotPromptTemplate -> ShowS
showsPrec :: Int -> FewShotPromptTemplate -> ShowS
$cshow :: FewShotPromptTemplate -> String
show :: FewShotPromptTemplate -> String
$cshowList :: [FewShotPromptTemplate] -> ShowS
showList :: [FewShotPromptTemplate] -> ShowS
Show, FewShotPromptTemplate -> FewShotPromptTemplate -> Bool
(FewShotPromptTemplate -> FewShotPromptTemplate -> Bool)
-> (FewShotPromptTemplate -> FewShotPromptTemplate -> Bool)
-> Eq FewShotPromptTemplate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FewShotPromptTemplate -> FewShotPromptTemplate -> Bool
== :: FewShotPromptTemplate -> FewShotPromptTemplate -> Bool
$c/= :: FewShotPromptTemplate -> FewShotPromptTemplate -> Bool
/= :: FewShotPromptTemplate -> FewShotPromptTemplate -> Bool
Eq)
renderFewShotPrompt :: FewShotPromptTemplate -> Either String Text
renderFewShotPrompt :: FewShotPromptTemplate -> Either String Text
renderFewShotPrompt FewShotPromptTemplate {[Map Text Text]
Text
fsPrefix :: FewShotPromptTemplate -> Text
fsExamples :: FewShotPromptTemplate -> [Map Text Text]
fsExampleTemplate :: FewShotPromptTemplate -> Text
fsExampleSeparator :: FewShotPromptTemplate -> Text
fsSuffix :: FewShotPromptTemplate -> Text
fsPrefix :: Text
fsExamples :: [Map Text Text]
fsExampleTemplate :: Text
fsExampleSeparator :: Text
fsSuffix :: Text
..} = do
[Text]
formattedExamples <-
(Map Text Text -> Either String Text)
-> [Map Text Text] -> Either String [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM
(\Map Text Text
ex -> Map Text Text -> Text -> Either String Text
interpolate Map Text Text
ex Text
fsExampleTemplate)
[Map Text Text]
fsExamples
let examplesText :: Text
examplesText = Text -> [Text] -> Text
T.intercalate Text
fsExampleSeparator [Text]
formattedExamples
Text -> Either String Text
forall a. a -> Either String a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Text
fsPrefix Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
examplesText Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
fsSuffix
interpolate :: HM.Map Text Text -> Text -> Either String Text
interpolate :: Map Text Text -> Text -> Either String Text
interpolate Map Text Text
vars Text
template = Text -> Either String Text
go Text
template
where
go :: Text -> Either String Text
go :: Text -> Either String Text
go Text
t =
case HasCallStack => Text -> Text -> (Text, Text)
Text -> Text -> (Text, Text)
T.breakOn Text
"{" Text
t of
(Text
before, Text
after) | Text -> Bool
T.null Text
after -> Text -> Either String Text
forall a b. b -> Either a b
Right Text
before
(Text
before, Text
after') ->
case HasCallStack => Text -> Text -> (Text, Text)
Text -> Text -> (Text, Text)
T.breakOn Text
"}" (Int -> Text -> Text
T.drop Int
1 Text
after') of
(Text
_, Text
after'') | Text -> Bool
T.null Text
after'' -> String -> Either String Text
forall a b. a -> Either a b
Left String
"Unclosed brace"
(Text
key, Text
after''') ->
let key' :: Text
key' = Text -> Text
T.strip Text
key
in case Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
HM.lookup Text
key' Map Text Text
vars of
Just Text
val -> do
Text
rest <- Text -> Either String Text
go (Int -> Text -> Text
T.drop Int
1 Text
after''')
Text -> Either String Text
forall a. a -> Either String a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Either String Text) -> Text -> Either String Text
forall a b. (a -> b) -> a -> b
$ Text
before Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
val Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rest
Maybe Text
Nothing -> String -> Either String Text
forall a b. a -> Either a b
Left (String -> Either String Text) -> String -> Either String Text
forall a b. (a -> b) -> a -> b
$ String
"Missing variable: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
key'
instance Runnable PromptTemplate where
type RunnableInput PromptTemplate = HM.Map Text Text
type RunnableOutput PromptTemplate = Text
invoke :: PromptTemplate
-> RunnableInput PromptTemplate
-> IO (Either String (RunnableOutput PromptTemplate))
invoke PromptTemplate
template RunnableInput PromptTemplate
variables = Either String Text -> IO (Either String Text)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String Text -> IO (Either String Text))
-> Either String Text -> IO (Either String Text)
forall a b. (a -> b) -> a -> b
$ PromptTemplate -> Map Text Text -> Either String Text
renderPrompt PromptTemplate
template Map Text Text
RunnableInput PromptTemplate
variables