I have used GWR for many years, with very good results. This is the illusttration how to use it:
(*http://library.wolfram.com/infocenter/MathSource/4738/*)GWR[F_,t_,M_: 32,precin_: 0]:=Module[{M1,G0,Gm,Gp,best,expr,τ=Log[2]/t,Fi,broken,prec},If[precin<=0,prec=21 M/10,prec=precin];
If[prec<=$MachinePrecision,prec=$MachinePrecision];
broken=False;
If[Precision[τ]<prec,τ=SetPrecision[τ,prec]];
Do[Fi[i]=N[F[i τ],prec],{i,1,2 M}];
M1=M;
Do[G0[n-1]=τ (2 n)!/(n! (n-1)!) Sum[Binomial[n,i] (-1)^i Fi[n+i],{i,0,n}];
If[Not[NumberQ[G0[n-1]]],M1=n-1;G0[n-1]=.;Break[]];,{n,1,M}];
Do[Gm[n]=0,{n,0,M1}];
best=G0[M1-1];
Do[Do[expr=G0[n+1]-G0[n];
If[Or[Not[NumberQ[expr]],expr==0],broken=True;Break[]];
expr=Gm[n+1]+(k+1)/expr;
Gp[n]=expr;
If[OddQ[k],If[n==M1-2-k,best=expr]];,{n,M1-2-k,0,-1}];
If[broken,Break[]];
Do[Gm[n]=G0[n];G0[n]=Gp[n],{n,0,M1-k}];,{k,0,M1-2}];
best]
SetAttributes[GWR,{Listable,NHoldAll}]
F[s_]:=12 (1-Exp[168 s]+168 Exp[180 s] s)/(-1+Exp[12 s]+Exp[168 s]-Exp[180 s]+2016 Exp[204 s] s^2);
t={10^-1,1,10,100,1000,10000,100000};
N[GWR[F,t,60],20]
N[GWR[F,t,80],20]
N[GWR[F,t,100],20]
N[GWR[F,t,120],20]
N[GWR[F,t,140],20]
You should increase the number of digits (the third calling parameter of GWR) until you get a satisfactory accuracy of the results. I notice that your original formula has one extra parenthesis, so that I am not sure if after removing it the formula for F is correct. But if it is, then I see that your transform may require a rather high value of the third parameter. Of course, instead of using a list of time values (t) you can just put a single value.
Leslaw