#!/usr/bin/env swipl
% UncloseAI - Prolog client for OpenAI-compatible APIs with streaming support

:- use_module(library(http/http_client)).
:- use_module(library(http/json)).
:- use_module(library(http/json_convert)).

:- json_object chat_message(role:atom, content:atom).
:- json_object chat_request(model:atom, messages:list, max_tokens:integer, temperature:float, stream:boolean).
:- json_object tts_request(model:atom, voice:atom, input:atom, response_format:atom).

% UncloseAI Client Structure
% uncloseai(Models, TtsEndpoints, ApiKey, Timeout, Debug)

% Create a new UncloseAI client
uncloseai_create(Client, Options) :-
    option(endpoints(ModelEndpoints), Options, []),
    option(tts_endpoints(TtsEndpointsIn), Options, []),
    option(api_key(ApiKey), Options, ''),
    option(timeout(Timeout), Options, 30),
    option(debug(Debug), Options, false),

    % Discover endpoints from environment if not provided
    (   ModelEndpoints = []
    ->  uncloseai_discover_env_endpoints('MODEL_ENDPOINT', ModelEnds)
    ;   ModelEnds = ModelEndpoints
    ),

    (   TtsEndpointsIn = []
    ->  uncloseai_discover_env_endpoints('TTS_ENDPOINT', TtsEnds)
    ;   TtsEnds = TtsEndpointsIn
    ),

    (   Debug = true
    ->  length(ModelEnds, MCount),
        format('[DEBUG] Initialized with ~w endpoint(s)~n', [MCount])
    ;   true
    ),

    uncloseai_discover_models(ModelEnds, Models, Debug),
    Client = uncloseai(Models, TtsEnds, ApiKey, Timeout, Debug).

% Discover endpoints from environment variables
uncloseai_discover_env_endpoints(Prefix, Endpoints) :-
    uncloseai_discover_env_endpoints_helper(Prefix, 1, Endpoints).

uncloseai_discover_env_endpoints_helper(Prefix, I, Endpoints) :-
    I < 10000,
    atom_concat(Prefix, '_', PrefixUnderscore),
    atom_concat(PrefixUnderscore, I, EnvVar),
    (   getenv(EnvVar, Endpoint)
    ->  I1 is I + 1,
        uncloseai_discover_env_endpoints_helper(Prefix, I1, RestEndpoints),
        Endpoints = [Endpoint|RestEndpoints]
    ;   Endpoints = []
    ).

% Discover models from endpoints
uncloseai_discover_models(Endpoints, Models, Debug) :-
    uncloseai_discover_models_helper(Endpoints, Models, Debug).

uncloseai_discover_models_helper([], [], _).
uncloseai_discover_models_helper([Endpoint|RestEndpoints], Models, Debug) :-
    (   Debug = true
    ->  format('[DEBUG] Discovering from: ~w~n', [Endpoint])
    ;   true
    ),
    catch(
        (atom_concat(Endpoint, '/models', URL),
         http_get(URL, ResponseJSON, [json_object(dict), timeout(10)]),
         get_dict(data, ResponseJSON, DataList),
         maplist(uncloseai_create_model_info(Endpoint, Debug), DataList, ModelInfos)),
        _Error,
        (   (Debug = true -> format('[DEBUG] Error discovering from ~w~n', [Endpoint]) ; true),
            ModelInfos = []
        )
    ),
    uncloseai_discover_models_helper(RestEndpoints, RestModels, Debug),
    append(ModelInfos, RestModels, Models).

uncloseai_create_model_info(Endpoint, Debug, ModelDict, model(Id, Endpoint, MaxTokens)) :-
    get_dict(id, ModelDict, Id),
    (   get_dict(max_model_len, ModelDict, MaxTokens)
    ->  true
    ;   MaxTokens = 8192
    ),
    (   Debug = true
    ->  format('[DEBUG] Discovered: ~w~n', [Id])
    ;   true
    ).

% List models
uncloseai_list_models(uncloseai(Models, _, _, _, _), Models).

% Resolve model
uncloseai_resolve_model(uncloseai(Models, _, _, _, _), ModelId, ModelInfo) :-
    (   Models = []
    ->  throw(error('No models available'))
    ;   (   ModelId = ''
        ->  Models = [ModelInfo|_]
        ;   (   member(ModelInfo, Models),
                ModelInfo = model(ModelId, _, _)
            ->  true
            ;   throw(error('Model not found'))
            )
        )
    ).

% Chat (non-streaming)
uncloseai_chat(Client, Messages, Response, Options) :-
    option(model(ModelId), Options, ''),
    option(max_tokens(MaxTokens), Options, 100),
    option(temperature(Temperature), Options, 0.7),

    uncloseai_resolve_model(Client, ModelId, model(MId, Endpoint, _)),

    Request = chat_request(MId, Messages, MaxTokens, Temperature, false),
    prolog_to_json(Request, JSON),

    atom_concat(Endpoint, '/chat/completions', URL),
    Client = uncloseai(_, _, ApiKey, _, _),
    (   ApiKey = ''
    ->  http_post(URL, json(JSON), Response, [json_object(dict)])
    ;   format(atom(AuthHeader), 'Bearer ~w', [ApiKey]),
        http_post(URL, json(JSON), Response, [json_object(dict), authorization(bearer(ApiKey))])
    ).

% Chat streaming (simplified - Prolog's streaming support is limited)
uncloseai_chat_stream(Client, Messages, Callback, Options) :-
    option(model(ModelId), Options, ''),
    option(max_tokens(MaxTokens), Options, 500),
    option(temperature(Temperature), Options, 0.7),

    uncloseai_resolve_model(Client, ModelId, model(MId, Endpoint, _)),

    Request = chat_request(MId, Messages, MaxTokens, Temperature, true),
    prolog_to_json(Request, JSON),

    atom_concat(Endpoint, '/chat/completions', URL),
    Client = uncloseai(_, _, ApiKey, _, Debug),

    % Note: SWI-Prolog's http_client doesn't have native SSE support
    % This is a simplified version - full SSE parsing would require custom stream handling
    catch(
        (   (   ApiKey = ''
            ->  http_post(URL, json(JSON), ResponseData, [])
            ;   format(atom(AuthHeader), 'Bearer ~w', [ApiKey]),
                http_post(URL, json(JSON), ResponseData, [authorization(bearer(ApiKey))])
            ),
            call(Callback, ResponseData)
        ),
        Error,
        (   (Debug = true -> format('[DEBUG] Stream error: ~w~n', [Error]) ; true))
    ).

% TTS
uncloseai_tts(Client, Text, AudioData, Options) :-
    option(voice(Voice), Options, alloy),
    option(model(Model), Options, 'tts-1'),
    option(response_format(Format), Options, mp3),

    Client = uncloseai(_, TtsEndpoints, ApiKey, _, _),
    (   TtsEndpoints = []
    ->  throw(error('No TTS endpoints available'))
    ;   TtsEndpoints = [Endpoint|_]
    ),

    Request = tts_request(Model, Voice, Text, Format),
    prolog_to_json(Request, JSON),

    atom_concat(Endpoint, '/audio/speech', URL),
    (   ApiKey = ''
    ->  http_post(URL, json(JSON), AudioData, [])
    ;   format(atom(AuthHeader), 'Bearer ~w', [ApiKey]),
        http_post(URL, json(JSON), AudioData, [authorization(bearer(ApiKey))])
    ).

% Demo when run as script
main :-
    writeln('=== UncloseAI Prolog Client (with Streaming) ===\n'),

    uncloseai_create(Client, [debug(true)]),

    uncloseai_list_models(Client, Models),
    (   Models = []
    ->  writeln('ERROR: No models discovered. Set environment variables:'),
        writeln('  MODEL_ENDPOINT_1, MODEL_ENDPOINT_2, etc.'),
        halt(1)
    ;   true
    ),

    length(Models, MCount),
    format('~nDiscovered ~w model(s):~n', [MCount]),
    forall(
        member(model(Id, _, MaxTokens), Models),
        format('  - ~w (max_tokens: ~w)~n', [Id, MaxTokens])
    ),
    nl,

    % Non-streaming chat
    writeln('=== Non-Streaming Chat ==='),
    catch(
        (uncloseai_chat(Client,
            [chat_message(system, 'You are a helpful AI assistant.'),
             chat_message(user, 'Explain quantum computing in one sentence.')],
            Response,
            []),
         get_dict(choices, Response, [Choice|_]),
         get_dict(message, Choice, Message),
         get_dict(content, Message, Content),
         format('Response: ~w~n~n', [Content])),
        Error,
        format('Error: ~w~n~n', [Error])
    ),

    % Streaming chat (simplified)
    writeln('=== Streaming Chat ==='),
    (   length(Models, Len), Len > 1
    ->  nth1(2, Models, model(ModelId, _, _))
    ;   Models = [model(ModelId, _, _)|_]
    ),
    format('Model: ~w~n', [ModelId]),
    write('Response: '),
    catch(
        uncloseai_chat_stream(Client,
            [chat_message(system, 'You are a coding assistant.'),
             chat_message(user, 'Write a Prolog predicate to check if a number is prime')],
            writeln,
            [model(ModelId), max_tokens(200)]),
        Error,
        format('~nError: ~w', [Error])
    ),
    nl, nl,

    % TTS
    Client = uncloseai(_, TtsEndpoints, _, _, _),
    (   TtsEndpoints = [_|_]
    ->  writeln('=== TTS Speech Generation ==='),
        catch(
            (uncloseai_tts(Client, 'Hello from UncloseAI Prolog client! This demonstrates streaming support.', AudioData, []),
             open('speech.mp3', write, Stream, [type(binary)]),
             write(Stream, AudioData),
             close(Stream),
             string_length(AudioData, Size),
             format('[OK] Speech file created: speech.mp3 (~w bytes)~n~n', [Size])),
            Error,
            format('[ERROR] TTS Error: ~w~n~n', [Error])
        )
    ;   true
    ),

    writeln('=== Examples Complete ==='),
    halt.

:- initialization(main).
